More work on the simplifier's inlining strategies
[ghc-hetmet.git] / compiler / main / DynFlags.hs
1 -- |
2 -- Dynamic flags
3 --
4 --
5 -- (c) The University of Glasgow 2005
6 --
7
8 -- Most flags are dynamic flags, which means they can change from
9 -- compilation to compilation using @OPTIONS_GHC@ pragmas, and in a
10 -- multi-session GHC each session can be using different dynamic
11 -- flags.  Dynamic flags can also be set at the prompt in GHCi.
12 module DynFlags (
13         -- * Dynamic flags and associated configuration types
14         DynFlag(..),
15         DynFlags(..),
16         HscTarget(..), isObjectTarget, defaultObjectTarget,
17         GhcMode(..), isOneShot,
18         GhcLink(..), isNoLink,
19         PackageFlag(..),
20         Option(..), showOpt,
21         DynLibLoader(..),
22         fFlags, xFlags,
23         dphPackage,
24         wayNames,
25
26         -- ** Manipulating DynFlags
27         defaultDynFlags,                -- DynFlags
28         initDynFlags,                   -- DynFlags -> IO DynFlags
29
30         dopt,                           -- DynFlag -> DynFlags -> Bool
31         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
32         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
33         getVerbFlag,
34         updOptLevel,
35         setTmpDir,
36         setPackageName,
37         doingTickyProfiling,
38
39         -- ** Parsing DynFlags
40         parseDynamicFlags,
41         parseDynamicNoPackageFlags,
42         allFlags,
43
44         supportedLanguages, languageOptions,
45
46         -- ** DynFlag C compiler options
47         machdepCCOpts, picCCOpts,
48
49         -- * Configuration of the core-to-core passes
50         CoreToDo(..),
51         SimplifierMode(..),
52         SimplifierSwitch(..),
53         FloatOutSwitches(..),
54         getCoreToDo,
55
56         -- * Configuration of the stg-to-stg passes
57         StgToDo(..),
58         getStgToDo,
59
60         -- * Compiler configuration suitable for display to the user
61         Printable(..),
62         compilerInfo
63   ) where
64
65 #include "HsVersions.h"
66
67 #ifndef OMIT_NATIVE_CODEGEN
68 import Platform
69 #endif
70 import Module
71 import PackageConfig
72 import PrelNames        ( mAIN )
73 import StaticFlags
74 import {-# SOURCE #-} Packages (PackageState)
75 import DriverPhases     ( Phase(..), phaseInputExt )
76 import Config
77 import CmdLineParser
78 import Constants        ( mAX_CONTEXT_REDUCTION_DEPTH )
79 import Panic
80 import Util
81 import Maybes           ( orElse )
82 import SrcLoc
83 import FastString
84 import FiniteMap
85 import BasicTypes       ( CompilerPhase )
86 import Outputable
87 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
88
89 import Data.IORef
90 import Control.Monad    ( when )
91
92 import Data.Char
93 import Data.List
94 import System.FilePath
95 import System.IO        ( stderr, hPutChar )
96
97 -- -----------------------------------------------------------------------------
98 -- DynFlags
99
100 -- | Enumerates the simple on-or-off dynamic flags
101 data DynFlag
102
103    -- debugging flags
104    = Opt_D_dump_cmm
105    | Opt_D_dump_cmmz
106    | Opt_D_dump_cmmz_pretty
107    | Opt_D_dump_cps_cmm
108    | Opt_D_dump_cvt_cmm
109    | Opt_D_dump_asm
110    | Opt_D_dump_asm_native
111    | Opt_D_dump_asm_liveness
112    | Opt_D_dump_asm_coalesce
113    | Opt_D_dump_asm_regalloc
114    | Opt_D_dump_asm_regalloc_stages
115    | Opt_D_dump_asm_conflicts
116    | Opt_D_dump_asm_stats
117    | Opt_D_dump_asm_expanded
118    | Opt_D_dump_cpranal
119    | Opt_D_dump_deriv
120    | Opt_D_dump_ds
121    | Opt_D_dump_flatC
122    | Opt_D_dump_foreign
123    | Opt_D_dump_inlinings
124    | Opt_D_dump_rule_firings
125    | Opt_D_dump_occur_anal
126    | Opt_D_dump_parsed
127    | Opt_D_dump_rn
128    | Opt_D_dump_simpl
129    | Opt_D_dump_simpl_iterations
130    | Opt_D_dump_simpl_phases
131    | Opt_D_dump_spec
132    | Opt_D_dump_prep
133    | Opt_D_dump_stg
134    | Opt_D_dump_stranal
135    | Opt_D_dump_tc
136    | Opt_D_dump_types
137    | Opt_D_dump_rules
138    | Opt_D_dump_cse
139    | Opt_D_dump_worker_wrapper
140    | Opt_D_dump_rn_trace
141    | Opt_D_dump_rn_stats
142    | Opt_D_dump_opt_cmm
143    | Opt_D_dump_simpl_stats
144    | Opt_D_dump_tc_trace
145    | Opt_D_dump_if_trace
146    | Opt_D_dump_splices
147    | Opt_D_dump_BCOs
148    | Opt_D_dump_vect
149    | Opt_D_dump_hpc
150    | Opt_D_dump_rtti
151    | Opt_D_source_stats
152    | Opt_D_verbose_core2core
153    | Opt_D_verbose_stg2stg
154    | Opt_D_dump_hi
155    | Opt_D_dump_hi_diffs
156    | Opt_D_dump_minimal_imports
157    | Opt_D_dump_mod_cycles
158    | Opt_D_dump_view_pattern_commoning
159    | Opt_D_faststring_stats
160    | Opt_DumpToFile                     -- ^ Append dump output to files instead of stdout.
161    | Opt_D_no_debug_output
162    | Opt_DoCoreLinting
163    | Opt_DoStgLinting
164    | Opt_DoCmmLinting
165    | Opt_DoAsmLinting
166
167    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
168    | Opt_WarnDuplicateExports
169    | Opt_WarnHiShadows
170    | Opt_WarnImplicitPrelude
171    | Opt_WarnIncompletePatterns
172    | Opt_WarnIncompletePatternsRecUpd
173    | Opt_WarnMissingFields
174    | Opt_WarnMissingMethods
175    | Opt_WarnMissingSigs
176    | Opt_WarnNameShadowing
177    | Opt_WarnOverlappingPatterns
178    | Opt_WarnSimplePatterns
179    | Opt_WarnTypeDefaults
180    | Opt_WarnMonomorphism
181    | Opt_WarnUnusedBinds
182    | Opt_WarnUnusedImports
183    | Opt_WarnUnusedMatches
184    | Opt_WarnWarningsDeprecations
185    | Opt_WarnDeprecatedFlags
186    | Opt_WarnDodgyExports
187    | Opt_WarnDodgyImports
188    | Opt_WarnOrphans
189    | Opt_WarnTabs
190    | Opt_WarnUnrecognisedPragmas
191    | Opt_WarnDodgyForeignImports
192    | Opt_WarnLazyUnliftedBindings
193    | Opt_WarnUnusedDoBind
194    | Opt_WarnWrongDoBind
195
196
197    -- language opts
198    | Opt_OverlappingInstances
199    | Opt_UndecidableInstances
200    | Opt_IncoherentInstances
201    | Opt_MonomorphismRestriction
202    | Opt_MonoPatBinds
203    | Opt_MonoLocalBinds
204    | Opt_ExtendedDefaultRules           -- Use GHC's extended rules for defaulting
205    | Opt_ForeignFunctionInterface
206    | Opt_UnliftedFFITypes
207    | Opt_GHCForeignImportPrim
208    | Opt_PArr                           -- Syntactic support for parallel arrays
209    | Opt_Arrows                         -- Arrow-notation syntax
210    | Opt_TemplateHaskell
211    | Opt_QuasiQuotes
212    | Opt_ImplicitParams
213    | Opt_Generics                       -- "Derivable type classes"
214    | Opt_ImplicitPrelude
215    | Opt_ScopedTypeVariables
216    | Opt_UnboxedTuples
217    | Opt_BangPatterns
218    | Opt_TypeFamilies
219    | Opt_OverloadedStrings
220    | Opt_DisambiguateRecordFields
221    | Opt_RecordWildCards
222    | Opt_RecordPuns
223    | Opt_ViewPatterns
224    | Opt_GADTs
225    | Opt_RelaxedPolyRec
226    | Opt_NPlusKPatterns
227
228    | Opt_StandaloneDeriving
229    | Opt_DeriveDataTypeable
230    | Opt_DeriveFunctor
231    | Opt_DeriveTraversable
232    | Opt_DeriveFoldable
233
234    | Opt_TypeSynonymInstances
235    | Opt_FlexibleContexts
236    | Opt_FlexibleInstances
237    | Opt_ConstrainedClassMethods
238    | Opt_MultiParamTypeClasses
239    | Opt_FunctionalDependencies
240    | Opt_UnicodeSyntax
241    | Opt_PolymorphicComponents
242    | Opt_ExistentialQuantification
243    | Opt_MagicHash
244    | Opt_EmptyDataDecls
245    | Opt_KindSignatures
246    | Opt_ParallelListComp
247    | Opt_TransformListComp
248    | Opt_GeneralizedNewtypeDeriving
249    | Opt_RecursiveDo
250    | Opt_DoRec
251    | Opt_PostfixOperators
252    | Opt_TupleSections
253    | Opt_PatternGuards
254    | Opt_LiberalTypeSynonyms
255    | Opt_Rank2Types
256    | Opt_RankNTypes
257    | Opt_ImpredicativeTypes
258    | Opt_TypeOperators
259    | Opt_PackageImports
260    | Opt_NewQualifiedOperators
261    | Opt_ExplicitForAll
262    | Opt_AlternativeLayoutRule
263
264    | Opt_PrintExplicitForalls
265
266    -- optimisation opts
267    | Opt_Strictness
268    | Opt_FullLaziness
269    | Opt_FloatIn
270    | Opt_Specialise
271    | Opt_StaticArgumentTransformation
272    | Opt_CSE
273    | Opt_LiberateCase
274    | Opt_SpecConstr
275    | Opt_DoLambdaEtaExpansion
276    | Opt_IgnoreAsserts
277    | Opt_DoEtaReduction
278    | Opt_CaseMerge
279    | Opt_UnboxStrictFields
280    | Opt_MethodSharing
281    | Opt_DictsCheap
282    | Opt_EnableRewriteRules             -- Apply rewrite rules during simplification
283    | Opt_Vectorise
284    | Opt_RegsGraph                      -- do graph coloring register allocation
285    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
286
287    -- Interface files
288    | Opt_IgnoreInterfacePragmas
289    | Opt_OmitInterfacePragmas
290    | Opt_ExposeAllUnfoldings
291
292    -- profiling opts
293    | Opt_AutoSccsOnAllToplevs
294    | Opt_AutoSccsOnExportedToplevs
295    | Opt_AutoSccsOnIndividualCafs
296
297    -- misc opts
298    | Opt_Cpp
299    | Opt_Pp
300    | Opt_ForceRecomp
301    | Opt_DryRun
302    | Opt_DoAsmMangling
303    | Opt_ExcessPrecision
304    | Opt_EagerBlackHoling
305    | Opt_ReadUserPackageConf
306    | Opt_NoHsMain
307    | Opt_SplitObjs
308    | Opt_StgStats
309    | Opt_HideAllPackages
310    | Opt_PrintBindResult
311    | Opt_Haddock
312    | Opt_HaddockOptions
313    | Opt_Hpc_No_Auto
314    | Opt_BreakOnException
315    | Opt_BreakOnError
316    | Opt_PrintEvldWithShow
317    | Opt_PrintBindContents
318    | Opt_GenManifest
319    | Opt_EmbedManifest
320    | Opt_EmitExternalCore
321    | Opt_SharedImplib
322    | Opt_BuildingCabalPackage
323
324         -- temporary flags
325    | Opt_RunCPS
326    | Opt_RunCPSZ
327    | Opt_ConvertToZipCfgAndBack
328    | Opt_AutoLinkPackages
329    | Opt_ImplicitImportQualified
330    | Opt_TryNewCodeGen
331
332    -- keeping stuff
333    | Opt_KeepHiDiffs
334    | Opt_KeepHcFiles
335    | Opt_KeepSFiles
336    | Opt_KeepRawSFiles
337    | Opt_KeepTmpFiles
338    | Opt_KeepRawTokenStream
339
340    deriving (Eq, Show)
341
342 -- | Contains not only a collection of 'DynFlag's but also a plethora of
343 -- information relating to the compilation of a single file or GHC session
344 data DynFlags = DynFlags {
345   ghcMode               :: GhcMode,
346   ghcLink               :: GhcLink,
347   coreToDo              :: Maybe [CoreToDo], -- reserved for -Ofile
348   stgToDo               :: Maybe [StgToDo],  -- similarly
349   hscTarget             :: HscTarget,
350   hscOutName            :: String,      -- ^ Name of the output file
351   extCoreName           :: String,      -- ^ Name of the .hcr output file
352   verbosity             :: Int,         -- ^ Verbosity level: see Note [Verbosity levels]
353   optLevel              :: Int,         -- ^ Optimisation level
354   simplPhases           :: Int,         -- ^ Number of simplifier phases
355   maxSimplIterations    :: Int,         -- ^ Max simplifier iterations
356   shouldDumpSimplPhase  :: SimplifierMode -> Bool,
357   ruleCheck             :: Maybe String,
358   strictnessBefore      :: [Int],       -- ^ Additional demand analysis
359
360   specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
361   specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
362   liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
363
364 #ifndef OMIT_NATIVE_CODEGEN
365   targetPlatform        :: Platform,    -- ^ The platform we're compiling for. Used by the NCG.
366 #endif
367   stolen_x86_regs       :: Int,
368   cmdlineHcIncludes     :: [String],    -- ^ @\-\#includes@
369   importPaths           :: [FilePath],
370   mainModIs             :: Module,
371   mainFunIs             :: Maybe String,
372   ctxtStkDepth          :: Int,         -- ^ Typechecker context stack depth
373
374   dphBackend            :: DPHBackend,
375
376   thisPackage           :: PackageId,   -- ^ name of package currently being compiled
377
378   -- ways
379   ways                  :: [Way],       -- ^ Way flags from the command line
380   buildTag              :: String,      -- ^ The global \"way\" (e.g. \"p\" for prof)
381   rtsBuildTag           :: String,      -- ^ The RTS \"way\"
382
383   -- For object splitting
384   splitInfo             :: Maybe (String,Int),
385
386   -- paths etc.
387   objectDir             :: Maybe String,
388   hiDir                 :: Maybe String,
389   stubDir               :: Maybe String,
390
391   objectSuf             :: String,
392   hcSuf                 :: String,
393   hiSuf                 :: String,
394
395   outputFile            :: Maybe String,
396   outputHi              :: Maybe String,
397   dynLibLoader          :: DynLibLoader,
398
399   -- | This is set by 'DriverPipeline.runPipeline' based on where
400   --    its output is going.
401   dumpPrefix            :: Maybe FilePath,
402
403   -- | Override the 'dumpPrefix' set by 'DriverPipeline.runPipeline'.
404   --    Set by @-ddump-file-prefix@
405   dumpPrefixForce       :: Maybe FilePath,
406
407   includePaths          :: [String],
408   libraryPaths          :: [String],
409   frameworkPaths        :: [String],    -- used on darwin only
410   cmdlineFrameworks     :: [String],    -- ditto
411   tmpDir                :: String,      -- no trailing '/'
412
413   ghcUsagePath          :: FilePath,    -- Filled in by SysTools
414   ghciUsagePath         :: FilePath,    -- ditto
415
416   hpcDir                :: String,      -- ^ Path to store the .mix files
417
418   -- options for particular phases
419   opt_L                 :: [String],
420   opt_P                 :: [String],
421   opt_F                 :: [String],
422   opt_c                 :: [String],
423   opt_m                 :: [String],
424   opt_a                 :: [String],
425   opt_l                 :: [String],
426   opt_windres           :: [String],
427
428   -- commands for particular phases
429   pgm_L                 :: String,
430   pgm_P                 :: (String,[Option]),
431   pgm_F                 :: String,
432   pgm_c                 :: (String,[Option]),
433   pgm_m                 :: (String,[Option]),
434   pgm_s                 :: (String,[Option]),
435   pgm_a                 :: (String,[Option]),
436   pgm_l                 :: (String,[Option]),
437   pgm_dll               :: (String,[Option]),
438   pgm_T                 :: String,
439   pgm_sysman            :: String,
440   pgm_windres           :: String,
441
442   --  For ghc -M
443   depMakefile           :: FilePath,
444   depIncludePkgDeps     :: Bool,
445   depExcludeMods        :: [ModuleName],
446   depSuffixes           :: [String],
447
448   --  Package flags
449   extraPkgConfs         :: [FilePath],
450   topDir                :: FilePath,    -- filled in by SysTools
451   systemPackageConfig   :: FilePath,    -- ditto
452         -- ^ The @-package-conf@ flags given on the command line, in the order
453         -- they appeared.
454
455   packageFlags          :: [PackageFlag],
456         -- ^ The @-package@ and @-hide-package@ flags from the command-line
457
458   -- Package state
459   -- NB. do not modify this field, it is calculated by
460   -- Packages.initPackages and Packages.updatePackages.
461   pkgDatabase           :: Maybe [PackageConfig],
462   pkgState              :: PackageState,
463
464   -- Temporary files
465   -- These have to be IORefs, because the defaultCleanupHandler needs to
466   -- know what to clean when an exception happens
467   filesToClean          :: IORef [FilePath],
468   dirsToClean           :: IORef (FiniteMap FilePath FilePath),
469
470   -- hsc dynamic flags
471   flags                 :: [DynFlag],
472
473   -- | Message output action: use "ErrUtils" instead of this if you can
474   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
475
476   haddockOptions :: Maybe String
477  }
478
479 wayNames :: DynFlags -> [WayName]
480 wayNames = map wayName . ways
481
482 -- | The target code type of the compilation (if any).
483 --
484 -- Whenever you change the target, also make sure to set 'ghcLink' to
485 -- something sensible.
486 --
487 -- 'HscNothing' can be used to avoid generating any output, however, note
488 -- that:
489 --
490 --  * This will not run the desugaring step, thus no warnings generated in
491 --    this step will be output.  In particular, this includes warnings related
492 --    to pattern matching.  You can run the desugarer manually using
493 --    'GHC.desugarModule'.
494 --
495 --  * If a program uses Template Haskell the typechecker may try to run code
496 --    from an imported module.  This will fail if no code has been generated
497 --    for this module.  You can use 'GHC.needsTemplateHaskell' to detect
498 --    whether this might be the case and choose to either switch to a
499 --    different target or avoid typechecking such modules.  (The latter may
500 --    preferable for security reasons.)
501 --
502 data HscTarget
503   = HscC           -- ^ Generate C code.
504   | HscAsm         -- ^ Generate assembly using the native code generator.
505   | HscJava        -- ^ Generate Java bytecode.
506   | HscInterpreted -- ^ Generate bytecode.  (Requires 'LinkInMemory')
507   | HscNothing     -- ^ Don't generate any code.  See notes above.
508   deriving (Eq, Show)
509
510 -- | Will this target result in an object file on the disk?
511 isObjectTarget :: HscTarget -> Bool
512 isObjectTarget HscC     = True
513 isObjectTarget HscAsm   = True
514 isObjectTarget _        = False
515
516 -- | The 'GhcMode' tells us whether we're doing multi-module
517 -- compilation (controlled via the "GHC" API) or one-shot
518 -- (single-module) compilation.  This makes a difference primarily to
519 -- the "Finder": in one-shot mode we look for interface files for
520 -- imported modules, but in multi-module mode we look for source files
521 -- in order to check whether they need to be recompiled.
522 data GhcMode
523   = CompManager         -- ^ @\-\-make@, GHCi, etc.
524   | OneShot             -- ^ @ghc -c Foo.hs@
525   | MkDepend            -- ^ @ghc -M@, see "Finder" for why we need this
526   deriving Eq
527
528 instance Outputable GhcMode where
529   ppr CompManager = ptext (sLit "CompManager")
530   ppr OneShot     = ptext (sLit "OneShot")
531   ppr MkDepend    = ptext (sLit "MkDepend")
532
533 isOneShot :: GhcMode -> Bool
534 isOneShot OneShot = True
535 isOneShot _other  = False
536
537 -- | What to do in the link step, if there is one.
538 data GhcLink
539   = NoLink              -- ^ Don't link at all
540   | LinkBinary          -- ^ Link object code into a binary
541   | LinkInMemory        -- ^ Use the in-memory dynamic linker (works for both
542                         --   bytecode and object code).
543   | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
544   deriving (Eq, Show)
545
546 isNoLink :: GhcLink -> Bool
547 isNoLink NoLink = True
548 isNoLink _      = False
549
550 -- Is it worth evaluating this Bool and caching it in the DynFlags value
551 -- during initDynFlags?
552 doingTickyProfiling :: DynFlags -> Bool
553 doingTickyProfiling _ = opt_Ticky
554   -- XXX -ticky is a static flag, because it implies -debug which is also
555   -- static.  If the way flags were made dynamic, we could fix this.
556
557 data PackageFlag
558   = ExposePackage  String
559   | ExposePackageId String
560   | HidePackage    String
561   | IgnorePackage  String
562   deriving Eq
563
564 defaultHscTarget :: HscTarget
565 defaultHscTarget = defaultObjectTarget
566
567 -- | The 'HscTarget' value corresponding to the default way to create
568 -- object files on the current platform.
569 defaultObjectTarget :: HscTarget
570 defaultObjectTarget
571   | cGhcWithNativeCodeGen == "YES"      =  HscAsm
572   | otherwise                           =  HscC
573
574 data DynLibLoader
575   = Deployable
576   | Wrapped (Maybe String)
577   | SystemDependent
578   deriving Eq
579
580 -- | Used by 'GHC.newSession' to partially initialize a new 'DynFlags' value
581 initDynFlags :: DynFlags -> IO DynFlags
582 initDynFlags dflags = do
583  -- someday these will be dynamic flags
584  ways <- readIORef v_Ways
585  refFilesToClean <- newIORef []
586  refDirsToClean <- newIORef emptyFM
587  return dflags{
588         ways            = ways,
589         buildTag        = mkBuildTag (filter (not . wayRTSOnly) ways),
590         rtsBuildTag     = mkBuildTag ways,
591         filesToClean    = refFilesToClean,
592         dirsToClean     = refDirsToClean
593         }
594
595 -- | The normal 'DynFlags'. Note that they is not suitable for use in this form
596 -- and must be fully initialized by 'GHC.newSession' first.
597 defaultDynFlags :: DynFlags
598 defaultDynFlags =
599      DynFlags {
600         ghcMode                 = CompManager,
601         ghcLink                 = LinkBinary,
602         coreToDo                = Nothing,
603         stgToDo                 = Nothing,
604         hscTarget               = defaultHscTarget,
605         hscOutName              = "",
606         extCoreName             = "",
607         verbosity               = 0,
608         optLevel                = 0,
609         simplPhases             = 2,
610         maxSimplIterations      = 4,
611         shouldDumpSimplPhase    = const False,
612         ruleCheck               = Nothing,
613         specConstrThreshold     = Just 200,
614         specConstrCount         = Just 3,
615         liberateCaseThreshold   = Just 200,
616         strictnessBefore        = [],
617
618 #ifndef OMIT_NATIVE_CODEGEN
619         targetPlatform          = defaultTargetPlatform,
620 #endif
621         stolen_x86_regs         = 4,
622         cmdlineHcIncludes       = [],
623         importPaths             = ["."],
624         mainModIs               = mAIN,
625         mainFunIs               = Nothing,
626         ctxtStkDepth            = mAX_CONTEXT_REDUCTION_DEPTH,
627
628         dphBackend              = DPHPar,
629
630         thisPackage             = mainPackageId,
631
632         objectDir               = Nothing,
633         hiDir                   = Nothing,
634         stubDir                 = Nothing,
635
636         objectSuf               = phaseInputExt StopLn,
637         hcSuf                   = phaseInputExt HCc,
638         hiSuf                   = "hi",
639
640         outputFile              = Nothing,
641         outputHi                = Nothing,
642         dynLibLoader            = SystemDependent,
643         dumpPrefix              = Nothing,
644         dumpPrefixForce         = Nothing,
645         includePaths            = [],
646         libraryPaths            = [],
647         frameworkPaths          = [],
648         cmdlineFrameworks       = [],
649         tmpDir                  = cDEFAULT_TMPDIR,
650
651         hpcDir                  = ".hpc",
652
653         opt_L                   = [],
654         opt_P                   = (if opt_PIC
655                                    then ["-D__PIC__", "-U __PIC__"] -- this list is reversed
656                                    else []),
657         opt_F                   = [],
658         opt_c                   = [],
659         opt_a                   = [],
660         opt_m                   = [],
661         opt_l                   = [],
662         opt_windres             = [],
663
664         extraPkgConfs           = [],
665         packageFlags            = [],
666         pkgDatabase             = Nothing,
667         pkgState                = panic "no package state yet: call GHC.setSessionDynFlags",
668         ways                    = panic "defaultDynFlags: No ways",
669         buildTag                = panic "defaultDynFlags: No buildTag",
670         rtsBuildTag             = panic "defaultDynFlags: No rtsBuildTag",
671         splitInfo               = Nothing,
672         -- initSysTools fills all these in
673         ghcUsagePath            = panic "defaultDynFlags: No ghciUsagePath",
674         ghciUsagePath           = panic "defaultDynFlags: No ghciUsagePath",
675         topDir                  = panic "defaultDynFlags: No topDir",
676         systemPackageConfig     = panic  "no systemPackageConfig: call GHC.setSessionDynFlags",
677         pgm_L                   = panic "defaultDynFlags: No pgm_L",
678         pgm_P                   = panic "defaultDynFlags: No pgm_P",
679         pgm_F                   = panic "defaultDynFlags: No pgm_F",
680         pgm_c                   = panic "defaultDynFlags: No pgm_c",
681         pgm_m                   = panic "defaultDynFlags: No pgm_m",
682         pgm_s                   = panic "defaultDynFlags: No pgm_s",
683         pgm_a                   = panic "defaultDynFlags: No pgm_a",
684         pgm_l                   = panic "defaultDynFlags: No pgm_l",
685         pgm_dll                 = panic "defaultDynFlags: No pgm_dll",
686         pgm_T                   = panic "defaultDynFlags: No pgm_T",
687         pgm_sysman              = panic "defaultDynFlags: No pgm_sysman",
688         pgm_windres             = panic "defaultDynFlags: No pgm_windres",
689         -- end of initSysTools values
690         -- ghc -M values
691         depMakefile       = "Makefile",
692         depIncludePkgDeps = False,
693         depExcludeMods    = [],
694         depSuffixes       = [],
695         -- end of ghc -M values
696         filesToClean   = panic "defaultDynFlags: No filesToClean",
697         dirsToClean    = panic "defaultDynFlags: No dirsToClean",
698         haddockOptions = Nothing,
699         flags = [
700             Opt_AutoLinkPackages,
701             Opt_ReadUserPackageConf,
702
703             Opt_MonoPatBinds,   -- Experimentally, I'm making this non-standard
704                                 -- behaviour the default, to see if anyone notices
705                                 -- SLPJ July 06
706
707             Opt_ImplicitPrelude,
708             Opt_MonomorphismRestriction,
709             Opt_NPlusKPatterns,
710
711             Opt_MethodSharing,
712
713             Opt_DoAsmMangling,
714
715             Opt_SharedImplib,
716
717             Opt_GenManifest,
718             Opt_EmbedManifest,
719             Opt_PrintBindContents
720             ]
721             ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
722                     -- The default -O0 options
723             ++ standardWarnings,
724
725         log_action = \severity srcSpan style msg ->
726                         case severity of
727                           SevInfo  -> printErrs (msg style)
728                           SevFatal -> printErrs (msg style)
729                           _        -> do 
730                                 hPutChar stderr '\n'
731                                 printErrs ((mkLocMessage srcSpan msg) style)
732                      -- careful (#2302): printErrs prints in UTF-8, whereas
733                      -- converting to string first and using hPutStr would
734                      -- just emit the low 8 bits of each unicode char.
735       }
736
737 {-
738 Note [Verbosity levels]
739 ~~~~~~~~~~~~~~~~~~~~~~~
740     0   |   print errors & warnings only
741     1   |   minimal verbosity: print "compiling M ... done." for each module.
742     2   |   equivalent to -dshow-passes
743     3   |   equivalent to existing "ghc -v"
744     4   |   "ghc -v -ddump-most"
745     5   |   "ghc -v -ddump-all"
746 -}
747
748 -- | Test whether a 'DynFlag' is set
749 dopt :: DynFlag -> DynFlags -> Bool
750 dopt f dflags  = f `elem` (flags dflags)
751
752 -- | Set a 'DynFlag'
753 dopt_set :: DynFlags -> DynFlag -> DynFlags
754 dopt_set dfs f = dfs{ flags = f : flags dfs }
755
756 -- | Unset a 'DynFlag'
757 dopt_unset :: DynFlags -> DynFlag -> DynFlags
758 dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
759
760 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
761 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
762         -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
763         -> [a]                  -- ^ Correctly ordered extracted options
764 getOpts dflags opts = reverse (opts dflags)
765         -- We add to the options from the front, so we need to reverse the list
766
767 -- | Gets the verbosity flag for the current verbosity level. This is fed to
768 -- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
769 getVerbFlag :: DynFlags -> String
770 getVerbFlag dflags
771   | verbosity dflags >= 3  = "-v"
772   | otherwise =  ""
773
774 setObjectDir, setHiDir, setStubDir, setOutputDir,
775          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
776          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
777          addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres,
778          addCmdlineFramework, addHaddockOpts
779    :: String -> DynFlags -> DynFlags
780 setOutputFile, setOutputHi, setDumpPrefixForce
781    :: Maybe String -> DynFlags -> DynFlags
782
783 setObjectDir  f d = d{ objectDir  = Just f}
784 setHiDir      f d = d{ hiDir      = Just f}
785 setStubDir    f d = d{ stubDir    = Just f, includePaths = f : includePaths d }
786   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
787   -- \#included from the .hc file when compiling with -fvia-C.
788 setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
789
790 setObjectSuf  f d = d{ objectSuf  = f}
791 setHiSuf      f d = d{ hiSuf      = f}
792 setHcSuf      f d = d{ hcSuf      = f}
793
794 setOutputFile f d = d{ outputFile = f}
795 setOutputHi   f d = d{ outputHi   = f}
796
797 parseDynLibLoaderMode f d =
798  case splitAt 8 f of
799    ("deploy", "")       -> d{ dynLibLoader = Deployable }
800    ("sysdep", "")       -> d{ dynLibLoader = SystemDependent }
801    ("wrapped", "")      -> d{ dynLibLoader = Wrapped Nothing }
802    ("wrapped:", "hard") -> d{ dynLibLoader = Wrapped Nothing }
803    ("wrapped:", flex)   -> d{ dynLibLoader = Wrapped (Just flex) }
804    _                    -> ghcError (CmdLineError ("Unknown dynlib loader: " ++ f))
805
806 setDumpPrefixForce f d = d { dumpPrefixForce = f}
807
808 -- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
809 -- Config.hs should really use Option.
810 setPgmP   f d = let (pgm:args) = words f in d{ pgm_P   = (pgm, map Option args)}
811
812 setPgmL   f d = d{ pgm_L   = f}
813 setPgmF   f d = d{ pgm_F   = f}
814 setPgmc   f d = d{ pgm_c   = (f,[])}
815 setPgmm   f d = d{ pgm_m   = (f,[])}
816 setPgms   f d = d{ pgm_s   = (f,[])}
817 setPgma   f d = d{ pgm_a   = (f,[])}
818 setPgml   f d = d{ pgm_l   = (f,[])}
819 setPgmdll f d = d{ pgm_dll = (f,[])}
820 setPgmwindres f d = d{ pgm_windres = f}
821
822 addOptL   f d = d{ opt_L   = f : opt_L d}
823 addOptP   f d = d{ opt_P   = f : opt_P d}
824 addOptF   f d = d{ opt_F   = f : opt_F d}
825 addOptc   f d = d{ opt_c   = f : opt_c d}
826 addOptm   f d = d{ opt_m   = f : opt_m d}
827 addOpta   f d = d{ opt_a   = f : opt_a d}
828 addOptl   f d = d{ opt_l   = f : opt_l d}
829 addOptwindres f d = d{ opt_windres = f : opt_windres d}
830
831 setDepMakefile :: FilePath -> DynFlags -> DynFlags
832 setDepMakefile f d = d { depMakefile = deOptDep f }
833
834 setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
835 setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
836
837 addDepExcludeMod :: String -> DynFlags -> DynFlags
838 addDepExcludeMod m d
839     = d { depExcludeMods = mkModuleName (deOptDep m) : depExcludeMods d }
840
841 addDepSuffix :: FilePath -> DynFlags -> DynFlags
842 addDepSuffix s d = d { depSuffixes = deOptDep s : depSuffixes d }
843
844 -- XXX Legacy code:
845 -- We used to use "-optdep-flag -optdeparg", so for legacy applications
846 -- we need to strip the "-optdep" off of the arg
847 deOptDep :: String -> String
848 deOptDep x = case stripPrefix "-optdep" x of
849              Just rest -> rest
850              Nothing -> x
851
852 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
853
854 addHaddockOpts f d = d{ haddockOptions = Just f}
855
856 -- -----------------------------------------------------------------------------
857 -- Command-line options
858
859 -- | When invoking external tools as part of the compilation pipeline, we
860 -- pass these a sequence of options on the command-line. Rather than
861 -- just using a list of Strings, we use a type that allows us to distinguish
862 -- between filepaths and 'other stuff'. The reason for this is that
863 -- this type gives us a handle on transforming filenames, and filenames only,
864 -- to whatever format they're expected to be on a particular platform.
865 data Option
866  = FileOption -- an entry that _contains_ filename(s) / filepaths.
867               String  -- a non-filepath prefix that shouldn't be
868                       -- transformed (e.g., "/out=")
869               String  -- the filepath/filename portion
870  | Option     String
871
872 showOpt :: Option -> String
873 showOpt (FileOption pre f) = pre ++ f
874 showOpt (Option s)  = s
875
876 -----------------------------------------------------------------------------
877 -- Setting the optimisation level
878
879 updOptLevel :: Int -> DynFlags -> DynFlags
880 -- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
881 updOptLevel n dfs
882   = dfs2{ optLevel = final_n }
883   where
884    final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
885    dfs1 = foldr (flip dopt_unset) dfs  remove_dopts
886    dfs2 = foldr (flip dopt_set)   dfs1 extra_dopts
887
888    extra_dopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
889    remove_dopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
890
891 optLevelFlags :: [([Int], DynFlag)]
892 optLevelFlags
893   = [ ([0],     Opt_IgnoreInterfacePragmas)
894     , ([0],     Opt_OmitInterfacePragmas)
895
896     , ([1,2],   Opt_IgnoreAsserts)
897     , ([1,2],   Opt_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
898                                          --              in PrelRules
899     , ([1,2],   Opt_DoEtaReduction)
900     , ([1,2],   Opt_CaseMerge)
901     , ([1,2],   Opt_Strictness)
902     , ([1,2],   Opt_CSE)
903     , ([1,2],   Opt_FullLaziness)
904     , ([1,2],   Opt_Specialise)
905     , ([1,2],   Opt_FloatIn)
906
907     , ([2],     Opt_LiberateCase)
908     , ([2],     Opt_SpecConstr)
909
910 --     , ([2],     Opt_StaticArgumentTransformation)
911 -- Max writes: I think it's probably best not to enable SAT with -O2 for the
912 -- 6.10 release. The version of SAT in HEAD at the moment doesn't incorporate
913 -- several improvements to the heuristics, and I'm concerned that without
914 -- those changes SAT will interfere with some attempts to write "high
915 -- performance Haskell", as we saw in some posts on Haskell-Cafe earlier
916 -- this year. In particular, the version in HEAD lacks the tail call
917 -- criterion, so many things that look like reasonable loops will be
918 -- turned into functions with extra (unneccesary) thunk creation.
919
920     , ([0,1,2], Opt_DoLambdaEtaExpansion)
921                 -- This one is important for a tiresome reason:
922                 -- we want to make sure that the bindings for data
923                 -- constructors are eta-expanded.  This is probably
924                 -- a good thing anyway, but it seems fragile.
925     ]
926
927 -- -----------------------------------------------------------------------------
928 -- Standard sets of warning options
929
930 standardWarnings :: [DynFlag]
931 standardWarnings
932     = [ Opt_WarnWarningsDeprecations,
933         Opt_WarnDeprecatedFlags,
934         Opt_WarnUnrecognisedPragmas,
935         Opt_WarnOverlappingPatterns,
936         Opt_WarnMissingFields,
937         Opt_WarnMissingMethods,
938         Opt_WarnDuplicateExports,
939         Opt_WarnLazyUnliftedBindings,
940         Opt_WarnDodgyForeignImports,
941         Opt_WarnWrongDoBind
942       ]
943
944 minusWOpts :: [DynFlag]
945 minusWOpts
946     = standardWarnings ++
947       [ Opt_WarnUnusedBinds,
948         Opt_WarnUnusedMatches,
949         Opt_WarnUnusedImports,
950         Opt_WarnIncompletePatterns,
951         Opt_WarnDodgyExports,
952         Opt_WarnDodgyImports
953       ]
954
955 minusWallOpts :: [DynFlag]
956 minusWallOpts
957     = minusWOpts ++
958       [ Opt_WarnTypeDefaults,
959         Opt_WarnNameShadowing,
960         Opt_WarnMissingSigs,
961         Opt_WarnHiShadows,
962         Opt_WarnOrphans,
963         Opt_WarnUnusedDoBind
964       ]
965
966 -- minuswRemovesOpts should be every warning option
967 minuswRemovesOpts :: [DynFlag]
968 minuswRemovesOpts
969     = minusWallOpts ++
970       [Opt_WarnImplicitPrelude,
971        Opt_WarnIncompletePatternsRecUpd,
972        Opt_WarnSimplePatterns,
973        Opt_WarnMonomorphism,
974        Opt_WarnUnrecognisedPragmas,
975        Opt_WarnTabs
976       ]
977
978 -- -----------------------------------------------------------------------------
979 -- CoreToDo:  abstraction of core-to-core passes to run.
980
981 data CoreToDo           -- These are diff core-to-core passes,
982                         -- which may be invoked in any order,
983                         -- as many times as you like.
984
985   = CoreDoSimplify      -- The core-to-core simplifier.
986         SimplifierMode
987         [SimplifierSwitch]
988                         -- Each run of the simplifier can take a different
989                         -- set of simplifier-specific flags.
990   | CoreDoFloatInwards
991   | CoreDoFloatOutwards FloatOutSwitches
992   | CoreLiberateCase
993   | CoreDoPrintCore
994   | CoreDoStaticArgs
995   | CoreDoStrictness
996   | CoreDoWorkerWrapper
997   | CoreDoSpecialising
998   | CoreDoSpecConstr
999   | CoreDoOldStrictness
1000   | CoreDoGlomBinds
1001   | CoreCSE
1002   | CoreDoRuleCheck CompilerPhase String   -- Check for non-application of rules
1003                                            -- matching this string
1004   | CoreDoVectorisation PackageId
1005   | CoreDoNothing                -- Useful when building up
1006   | CoreDoPasses [CoreToDo]      -- lists of these things
1007
1008
1009 data SimplifierMode             -- See comments in SimplMonad
1010   = SimplGently
1011         { sm_rules :: Bool      -- Whether RULES are enabled 
1012         , sm_inline :: Bool }   -- Whether inlining is enabled
1013
1014   | SimplPhase 
1015         { sm_num :: Int           -- Phase number; counts downward so 0 is last phase
1016         , sm_names :: [String] }  -- Name(s) of the phase
1017
1018 instance Outputable SimplifierMode where
1019     ppr (SimplPhase { sm_num = n, sm_names = ss })
1020        = int n <+> brackets (text (concat $ intersperse "," ss))
1021     ppr (SimplGently { sm_rules = r, sm_inline = i }) 
1022        = ptext (sLit "gentle") <> 
1023            brackets (pp_flag r (sLit "rules") <> comma <>
1024                      pp_flag i (sLit "inline"))
1025          where
1026            pp_flag f s = ppUnless f (ptext (sLit "no")) <+> ptext s
1027
1028 data SimplifierSwitch
1029   = MaxSimplifierIterations Int
1030   | NoCaseOfCase
1031
1032 data FloatOutSwitches = FloatOutSwitches {
1033         floatOutLambdas :: Bool,     -- ^ True <=> float lambdas to top level
1034         floatOutConstants :: Bool    -- ^ True <=> float constants to top level,
1035                                      --            even if they do not escape a lambda
1036     }
1037
1038 instance Outputable FloatOutSwitches where
1039     ppr = pprFloatOutSwitches
1040
1041 pprFloatOutSwitches :: FloatOutSwitches -> SDoc
1042 pprFloatOutSwitches sw = pp_not (floatOutLambdas sw) <+> text "lambdas" <> comma
1043                      <+> pp_not (floatOutConstants sw) <+> text "constants"
1044   where
1045     pp_not True  = empty
1046     pp_not False = text "not"
1047
1048 -- | Switches that specify the minimum amount of floating out
1049 -- gentleFloatOutSwitches :: FloatOutSwitches
1050 -- gentleFloatOutSwitches = FloatOutSwitches False False
1051
1052 -- | Switches that do not specify floating out of lambdas, just of constants
1053 constantsOnlyFloatOutSwitches :: FloatOutSwitches
1054 constantsOnlyFloatOutSwitches = FloatOutSwitches False True
1055
1056
1057 -- The core-to-core pass ordering is derived from the DynFlags:
1058 runWhen :: Bool -> CoreToDo -> CoreToDo
1059 runWhen True  do_this = do_this
1060 runWhen False _       = CoreDoNothing
1061
1062 runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo
1063 runMaybe (Just x) f = f x
1064 runMaybe Nothing  _ = CoreDoNothing
1065
1066 getCoreToDo :: DynFlags -> [CoreToDo]
1067 getCoreToDo dflags
1068   | Just todo <- coreToDo dflags = todo -- set explicitly by user
1069   | otherwise = core_todo
1070   where
1071     opt_level     = optLevel dflags
1072     phases        = simplPhases dflags
1073     max_iter      = maxSimplIterations dflags
1074     strictness    = dopt Opt_Strictness dflags
1075     full_laziness = dopt Opt_FullLaziness dflags
1076     do_specialise = dopt Opt_Specialise dflags
1077     do_float_in   = dopt Opt_FloatIn dflags
1078     cse           = dopt Opt_CSE dflags
1079     spec_constr   = dopt Opt_SpecConstr dflags
1080     liberate_case = dopt Opt_LiberateCase dflags
1081     rule_check    = ruleCheck dflags
1082     static_args   = dopt Opt_StaticArgumentTransformation dflags
1083
1084     maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase)
1085
1086     maybe_strictness_before phase
1087       = runWhen (phase `elem` strictnessBefore dflags) CoreDoStrictness
1088
1089     simpl_phase phase names iter
1090       = CoreDoPasses
1091           [ maybe_strictness_before phase,
1092             CoreDoSimplify (SimplPhase phase names) [
1093               MaxSimplifierIterations iter
1094             ],
1095             maybe_rule_check phase
1096           ]
1097
1098     vectorisation
1099       = runWhen (dopt Opt_Vectorise dflags)
1100         $ CoreDoPasses [ simpl_gently, CoreDoVectorisation (dphPackage dflags) ]
1101
1102
1103                 -- By default, we have 2 phases before phase 0.
1104
1105                 -- Want to run with inline phase 2 after the specialiser to give
1106                 -- maximum chance for fusion to work before we inline build/augment
1107                 -- in phase 1.  This made a difference in 'ansi' where an
1108                 -- overloaded function wasn't inlined till too late.
1109
1110                 -- Need phase 1 so that build/augment get
1111                 -- inlined.  I found that spectral/hartel/genfft lost some useful
1112                 -- strictness in the function sumcode' if augment is not inlined
1113                 -- before strictness analysis runs
1114     simpl_phases = CoreDoPasses [ simpl_phase phase ["main"] max_iter
1115                                   | phase <- [phases, phases-1 .. 1] ]
1116
1117
1118         -- initial simplify: mk specialiser happy: minimum effort please
1119     simpl_gently = CoreDoSimplify 
1120                        (SimplGently { sm_rules = True, sm_inline = False })
1121                        [
1122                         --      Simplify "gently"
1123                         -- Don't inline anything till full laziness has bitten
1124                         -- In particular, inlining wrappers inhibits floating
1125                         -- e.g. ...(case f x of ...)...
1126                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
1127                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
1128                         -- and now the redex (f x) isn't floatable any more
1129                         -- Similarly, don't apply any rules until after full
1130                         -- laziness.  Notably, list fusion can prevent floating.
1131
1132             NoCaseOfCase,       -- Don't do case-of-case transformations.
1133                                 -- This makes full laziness work better
1134             MaxSimplifierIterations max_iter
1135         ]
1136
1137     core_todo =
1138      if opt_level == 0 then
1139        [vectorisation,
1140         simpl_phase 0 ["final"] max_iter]
1141      else {- opt_level >= 1 -} [
1142
1143     -- We want to do the static argument transform before full laziness as it
1144     -- may expose extra opportunities to float things outwards. However, to fix
1145     -- up the output of the transformation we need at do at least one simplify
1146     -- after this before anything else
1147         runWhen static_args (CoreDoPasses [ simpl_gently, CoreDoStaticArgs ]),
1148
1149         -- We run vectorisation here for now, but we might also try to run
1150         -- it later
1151         vectorisation,
1152
1153         -- initial simplify: mk specialiser happy: minimum effort please
1154         simpl_gently,
1155
1156         -- Specialisation is best done before full laziness
1157         -- so that overloaded functions have all their dictionary lambdas manifest
1158         runWhen do_specialise CoreDoSpecialising,
1159
1160         runWhen full_laziness (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
1161                 -- Was: gentleFloatOutSwitches  
1162                 -- I have no idea why, but not floating constants to top level is
1163                 -- very bad in some cases. 
1164                 -- Notably: p_ident in spectral/rewrite
1165                 --          Changing from "gentle" to "constantsOnly" improved
1166                 --          rewrite's allocation by 19%, and made  0.0% difference
1167                 --          to any other nofib benchmark
1168
1169         runWhen do_float_in CoreDoFloatInwards,
1170
1171         simpl_phases,
1172
1173                 -- Phase 0: allow all Ids to be inlined now
1174                 -- This gets foldr inlined before strictness analysis
1175
1176                 -- At least 3 iterations because otherwise we land up with
1177                 -- huge dead expressions because of an infelicity in the
1178                 -- simpifier.
1179                 --      let k = BIG in foldr k z xs
1180                 -- ==>  let k = BIG in letrec go = \xs -> ...(k x).... in go xs
1181                 -- ==>  let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs
1182                 -- Don't stop now!
1183         simpl_phase 0 ["main"] (max max_iter 3),
1184
1185         runWhen strictness (CoreDoPasses [
1186                 CoreDoStrictness,
1187                 CoreDoWorkerWrapper,
1188                 CoreDoGlomBinds,
1189                 simpl_phase 0 ["post-worker-wrapper"] max_iter
1190                 ]),
1191
1192         runWhen full_laziness
1193           (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
1194                 -- nofib/spectral/hartel/wang doubles in speed if you
1195                 -- do full laziness late in the day.  It only happens
1196                 -- after fusion and other stuff, so the early pass doesn't
1197                 -- catch it.  For the record, the redex is
1198                 --        f_el22 (f_el21 r_midblock)
1199
1200
1201         runWhen cse CoreCSE,
1202                 -- We want CSE to follow the final full-laziness pass, because it may
1203                 -- succeed in commoning up things floated out by full laziness.
1204                 -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
1205
1206         runWhen do_float_in CoreDoFloatInwards,
1207
1208         maybe_rule_check 0,
1209
1210                 -- Case-liberation for -O2.  This should be after
1211                 -- strictness analysis and the simplification which follows it.
1212         runWhen liberate_case (CoreDoPasses [
1213             CoreLiberateCase,
1214             simpl_phase 0 ["post-liberate-case"] max_iter
1215             ]),         -- Run the simplifier after LiberateCase to vastly
1216                         -- reduce the possiblility of shadowing
1217                         -- Reason: see Note [Shadowing] in SpecConstr.lhs
1218
1219         runWhen spec_constr CoreDoSpecConstr,
1220
1221         maybe_rule_check 0,
1222
1223         -- Final clean-up simplification:
1224         simpl_phase 0 ["final"] max_iter
1225      ]
1226
1227 -- -----------------------------------------------------------------------------
1228 -- StgToDo:  abstraction of stg-to-stg passes to run.
1229
1230 data StgToDo
1231   = StgDoMassageForProfiling  -- should be (next to) last
1232   -- There's also setStgVarInfo, but its absolute "lastness"
1233   -- is so critical that it is hardwired in (no flag).
1234   | D_stg_stats
1235
1236 getStgToDo :: DynFlags -> [StgToDo]
1237 getStgToDo dflags
1238   | Just todo <- stgToDo dflags = todo -- set explicitly by user
1239   | otherwise = todo2
1240   where
1241         stg_stats = dopt Opt_StgStats dflags
1242
1243         todo1 = if stg_stats then [D_stg_stats] else []
1244
1245         todo2 | WayProf `elem` wayNames dflags
1246               = StgDoMassageForProfiling : todo1
1247               | otherwise
1248               = todo1
1249
1250 -- -----------------------------------------------------------------------------
1251 -- DynFlags parser
1252
1253 allFlags :: [String]
1254 allFlags = map ('-':) $
1255            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
1256            map ("fno-"++) flags ++
1257            map ("f"++) flags ++
1258            map ("X"++) supportedLanguages ++
1259            map ("XNo"++) supportedLanguages
1260     where ok (PrefixPred _ _) = False
1261           ok _ = True
1262           flags = [ name | (name, _, _) <- fFlags ]
1263
1264 dynamic_flags :: [Flag DynP]
1265 dynamic_flags = [
1266     Flag "n"              (NoArg  (setDynFlag Opt_DryRun)) Supported
1267   , Flag "cpp"            (NoArg  (setDynFlag Opt_Cpp)) Supported
1268   , Flag "F"              (NoArg  (setDynFlag Opt_Pp)) Supported
1269   , Flag "#include"       (HasArg (addCmdlineHCInclude))
1270                              (Deprecated "No longer has any effect")
1271   , Flag "v"              (OptIntSuffix setVerbosity) Supported
1272
1273         ------- Specific phases  --------------------------------------------
1274   , Flag "pgmL"           (HasArg (upd . setPgmL)) Supported
1275   , Flag "pgmP"           (HasArg (upd . setPgmP)) Supported
1276   , Flag "pgmF"           (HasArg (upd . setPgmF)) Supported
1277   , Flag "pgmc"           (HasArg (upd . setPgmc)) Supported
1278   , Flag "pgmm"           (HasArg (upd . setPgmm)) Supported
1279   , Flag "pgms"           (HasArg (upd . setPgms)) Supported
1280   , Flag "pgma"           (HasArg (upd . setPgma)) Supported
1281   , Flag "pgml"           (HasArg (upd . setPgml)) Supported
1282   , Flag "pgmdll"         (HasArg (upd . setPgmdll)) Supported
1283   , Flag "pgmwindres"     (HasArg (upd . setPgmwindres)) Supported
1284
1285   , Flag "optL"           (HasArg (upd . addOptL)) Supported
1286   , Flag "optP"           (HasArg (upd . addOptP)) Supported
1287   , Flag "optF"           (HasArg (upd . addOptF)) Supported
1288   , Flag "optc"           (HasArg (upd . addOptc)) Supported
1289   , Flag "optm"           (HasArg (upd . addOptm)) Supported
1290   , Flag "opta"           (HasArg (upd . addOpta)) Supported
1291   , Flag "optl"           (HasArg (upd . addOptl)) Supported
1292   , Flag "optwindres"     (HasArg (upd . addOptwindres)) Supported
1293
1294   , Flag "split-objs"
1295          (NoArg (if can_split then setDynFlag Opt_SplitObjs else return ()))
1296          Supported
1297
1298         -------- ghc -M -----------------------------------------------------
1299   , Flag "dep-suffix"               (HasArg (upd . addDepSuffix)) Supported
1300   , Flag "optdep-s"                 (HasArg (upd . addDepSuffix))
1301          (Deprecated "Use -dep-suffix instead")
1302   , Flag "dep-makefile"             (HasArg (upd . setDepMakefile)) Supported
1303   , Flag "optdep-f"                 (HasArg (upd . setDepMakefile))
1304          (Deprecated "Use -dep-makefile instead")
1305   , Flag "optdep-w"                 (NoArg  (return ()))
1306          (Deprecated "-optdep-w doesn't do anything")
1307   , Flag "include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True))) Supported
1308   , Flag "optdep--include-prelude"  (NoArg  (upd (setDepIncludePkgDeps True)))
1309          (Deprecated "Use -include-pkg-deps instead")
1310   , Flag "optdep--include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True)))
1311          (Deprecated "Use -include-pkg-deps instead")
1312   , Flag "exclude-module"           (HasArg (upd . addDepExcludeMod)) Supported
1313   , Flag "optdep--exclude-module"   (HasArg (upd . addDepExcludeMod))
1314          (Deprecated "Use -exclude-module instead")
1315   , Flag "optdep-x"                 (HasArg (upd . addDepExcludeMod))
1316          (Deprecated "Use -exclude-module instead")
1317
1318         -------- Linking ----------------------------------------------------
1319   , Flag "c"              (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1320          Supported
1321   , Flag "no-link"        (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1322          (Deprecated "Use -c instead")
1323   , Flag "shared"         (NoArg (upd $ \d -> d{ ghcLink=LinkDynLib } ))
1324          Supported
1325   , Flag "dynload"        (HasArg (upd . parseDynLibLoaderMode))
1326          Supported
1327
1328         ------- Libraries ---------------------------------------------------
1329   , Flag "L"              (Prefix addLibraryPath ) Supported
1330   , Flag "l"              (AnySuffix (\s -> do upd (addOptl s))) Supported
1331
1332         ------- Frameworks --------------------------------------------------
1333         -- -framework-path should really be -F ...
1334   , Flag "framework-path" (HasArg addFrameworkPath ) Supported
1335   , Flag "framework"      (HasArg (upd . addCmdlineFramework)) Supported
1336
1337         ------- Output Redirection ------------------------------------------
1338   , Flag "odir"           (HasArg (upd . setObjectDir)) Supported
1339   , Flag "o"              (SepArg (upd . setOutputFile . Just)) Supported
1340   , Flag "ohi"            (HasArg (upd . setOutputHi   . Just )) Supported
1341   , Flag "osuf"           (HasArg (upd . setObjectSuf)) Supported
1342   , Flag "hcsuf"          (HasArg (upd . setHcSuf)) Supported
1343   , Flag "hisuf"          (HasArg (upd . setHiSuf)) Supported
1344   , Flag "hidir"          (HasArg (upd . setHiDir)) Supported
1345   , Flag "tmpdir"         (HasArg (upd . setTmpDir)) Supported
1346   , Flag "stubdir"        (HasArg (upd . setStubDir)) Supported
1347   , Flag "outputdir"      (HasArg (upd . setOutputDir)) Supported
1348   , Flag "ddump-file-prefix" (HasArg (upd . setDumpPrefixForce . Just))
1349          Supported
1350
1351         ------- Keeping temporary files -------------------------------------
1352      -- These can be singular (think ghc -c) or plural (think ghc --make)
1353   , Flag "keep-hc-file"     (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1354   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1355   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1356   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1357   , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1358   , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1359      -- This only makes sense as plural
1360   , Flag "keep-tmp-files"   (NoArg (setDynFlag Opt_KeepTmpFiles)) Supported
1361
1362         ------- Miscellaneous ----------------------------------------------
1363   , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages)) Supported
1364   , Flag "no-hs-main"     (NoArg (setDynFlag Opt_NoHsMain)) Supported
1365   , Flag "main-is"        (SepArg setMainIs ) Supported
1366   , Flag "haddock"        (NoArg (setDynFlag Opt_Haddock)) Supported
1367   , Flag "haddock-opts"   (HasArg (upd . addHaddockOpts)) Supported
1368   , Flag "hpcdir"         (SepArg setOptHpcDir) Supported
1369
1370         ------- recompilation checker --------------------------------------
1371   , Flag "recomp"         (NoArg (unSetDynFlag Opt_ForceRecomp))
1372          (Deprecated "Use -fno-force-recomp instead")
1373   , Flag "no-recomp"      (NoArg (setDynFlag   Opt_ForceRecomp))
1374          (Deprecated "Use -fforce-recomp instead")
1375
1376         ------ HsCpp opts ---------------------------------------------------
1377   , Flag "D"              (AnySuffix (upd . addOptP)) Supported
1378   , Flag "U"              (AnySuffix (upd . addOptP)) Supported
1379
1380         ------- Include/Import Paths ----------------------------------------
1381   , Flag "I"              (Prefix    addIncludePath) Supported
1382   , Flag "i"              (OptPrefix addImportPath ) Supported
1383
1384         ------ Debugging ----------------------------------------------------
1385   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats)) Supported
1386
1387   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
1388          Supported
1389   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
1390          Supported
1391   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
1392          Supported
1393   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
1394          Supported
1395   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
1396          Supported
1397   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
1398          Supported
1399   , Flag "ddump-asm-native"        (setDumpFlag Opt_D_dump_asm_native)
1400          Supported
1401   , Flag "ddump-asm-liveness"      (setDumpFlag Opt_D_dump_asm_liveness)
1402          Supported
1403   , Flag "ddump-asm-coalesce"      (setDumpFlag Opt_D_dump_asm_coalesce)
1404          Supported
1405   , Flag "ddump-asm-regalloc"      (setDumpFlag Opt_D_dump_asm_regalloc)
1406          Supported
1407   , Flag "ddump-asm-conflicts"     (setDumpFlag Opt_D_dump_asm_conflicts)
1408          Supported
1409   , Flag "ddump-asm-regalloc-stages"
1410                                  (setDumpFlag Opt_D_dump_asm_regalloc_stages)
1411          Supported
1412   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
1413          Supported
1414   , Flag "ddump-asm-expanded"      (setDumpFlag Opt_D_dump_asm_expanded)
1415          Supported
1416   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
1417          Supported
1418   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
1419          Supported
1420   , Flag "ddump-ds"                (setDumpFlag Opt_D_dump_ds)
1421          Supported
1422   , Flag "ddump-flatC"             (setDumpFlag Opt_D_dump_flatC)
1423          Supported
1424   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
1425          Supported
1426   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
1427          Supported
1428   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
1429          Supported
1430   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
1431          Supported
1432   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
1433          Supported
1434   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
1435          Supported
1436   , Flag "ddump-simpl"             (setDumpFlag Opt_D_dump_simpl)
1437          Supported
1438   , Flag "ddump-simpl-iterations"  (setDumpFlag Opt_D_dump_simpl_iterations)
1439          Supported
1440   , Flag "ddump-simpl-phases"      (OptPrefix setDumpSimplPhases)
1441          Supported
1442   , Flag "ddump-spec"              (setDumpFlag Opt_D_dump_spec)
1443          Supported
1444   , Flag "ddump-prep"              (setDumpFlag Opt_D_dump_prep)
1445          Supported
1446   , Flag "ddump-stg"               (setDumpFlag Opt_D_dump_stg)
1447          Supported
1448   , Flag "ddump-stranal"           (setDumpFlag Opt_D_dump_stranal)
1449          Supported
1450   , Flag "ddump-tc"                (setDumpFlag Opt_D_dump_tc)
1451          Supported
1452   , Flag "ddump-types"             (setDumpFlag Opt_D_dump_types)
1453          Supported
1454   , Flag "ddump-rules"             (setDumpFlag Opt_D_dump_rules)
1455          Supported
1456   , Flag "ddump-cse"               (setDumpFlag Opt_D_dump_cse)
1457          Supported
1458   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
1459          Supported
1460   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
1461          Supported
1462   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
1463          Supported
1464   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
1465          Supported
1466   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
1467          Supported
1468   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
1469          Supported
1470   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
1471          Supported
1472   , Flag "ddump-simpl-stats"       (setDumpFlag Opt_D_dump_simpl_stats)
1473          Supported
1474   , Flag "ddump-bcos"              (setDumpFlag Opt_D_dump_BCOs)
1475          Supported
1476   , Flag "dsource-stats"           (setDumpFlag Opt_D_source_stats)
1477          Supported
1478   , Flag "dverbose-core2core"      (NoArg (do { setVerbosity (Just 2)
1479                                               ; setVerboseCore2Core }))
1480          Supported
1481   , Flag "dverbose-stg2stg"        (setDumpFlag Opt_D_verbose_stg2stg)
1482          Supported
1483   , Flag "ddump-hi"                (setDumpFlag Opt_D_dump_hi)
1484          Supported
1485   , Flag "ddump-minimal-imports"   (setDumpFlag Opt_D_dump_minimal_imports)
1486          Supported
1487   , Flag "ddump-vect"              (setDumpFlag Opt_D_dump_vect)
1488          Supported
1489   , Flag "ddump-hpc"               (setDumpFlag Opt_D_dump_hpc)
1490          Supported
1491   , Flag "ddump-mod-cycles"        (setDumpFlag Opt_D_dump_mod_cycles)
1492          Supported
1493   , Flag "ddump-view-pattern-commoning" (setDumpFlag Opt_D_dump_view_pattern_commoning)
1494          Supported
1495   , Flag "ddump-to-file"           (setDumpFlag Opt_DumpToFile)
1496          Supported
1497   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
1498          Supported
1499   , Flag "ddump-rtti"              (setDumpFlag Opt_D_dump_rtti)
1500          Supported
1501
1502   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
1503          Supported
1504   , Flag "dstg-lint"               (NoArg (setDynFlag Opt_DoStgLinting))
1505          Supported
1506   , Flag "dcmm-lint"               (NoArg (setDynFlag Opt_DoCmmLinting))
1507          Supported
1508   , Flag "dasm-lint"               (NoArg (setDynFlag Opt_DoAsmLinting))
1509          Supported
1510   , Flag "dshow-passes"
1511          (NoArg (do forceRecompile
1512                     setVerbosity (Just 2)))
1513          Supported
1514   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
1515          Supported
1516
1517         ------ Machine dependant (-m<blah>) stuff ---------------------------
1518
1519   , Flag "monly-2-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 2}) ))
1520          Supported
1521   , Flag "monly-3-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 3}) ))
1522          Supported
1523   , Flag "monly-4-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 4}) ))
1524          Supported
1525
1526      ------ Warning opts -------------------------------------------------
1527   , Flag "W"      (NoArg (mapM_ setDynFlag   minusWOpts))
1528          Supported
1529   , Flag "Werror" (NoArg (setDynFlag         Opt_WarnIsError))
1530          Supported
1531   , Flag "Wwarn"  (NoArg (unSetDynFlag       Opt_WarnIsError))
1532          Supported
1533   , Flag "Wall"   (NoArg (mapM_ setDynFlag   minusWallOpts))
1534          Supported
1535   , Flag "Wnot"   (NoArg (mapM_ unSetDynFlag minusWallOpts))
1536          (Deprecated "Use -w instead")
1537   , Flag "w"      (NoArg (mapM_ unSetDynFlag minuswRemovesOpts))
1538          Supported
1539
1540         ------ Optimisation flags ------------------------------------------
1541   , Flag "O"      (NoArg (upd (setOptLevel 1))) Supported
1542   , Flag "Onot"   (NoArg (upd (setOptLevel 0)))
1543          (Deprecated "Use -O0 instead")
1544   , Flag "Odph"   (NoArg (upd setDPHOpt)) Supported
1545   , Flag "O"      (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1546          Supported
1547                 -- If the number is missing, use 1
1548
1549   , Flag "fsimplifier-phases"
1550          (IntSuffix (\n -> upd (\dfs -> dfs{ simplPhases = n })))
1551          Supported
1552   , Flag "fmax-simplifier-iterations"
1553          (IntSuffix (\n -> upd (\dfs -> dfs{ maxSimplIterations = n })))
1554          Supported
1555
1556   , Flag "fspec-constr-threshold"
1557          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrThreshold = Just n })))
1558          Supported
1559   , Flag "fno-spec-constr-threshold"
1560          (NoArg (upd (\dfs -> dfs{ specConstrThreshold = Nothing })))
1561          Supported
1562   , Flag "fspec-constr-count"
1563          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrCount = Just n })))
1564          Supported
1565   , Flag "fno-spec-constr-count"
1566          (NoArg (upd (\dfs -> dfs{ specConstrCount = Nothing })))
1567          Supported
1568   , Flag "fliberate-case-threshold"
1569          (IntSuffix (\n -> upd (\dfs -> dfs{ liberateCaseThreshold = Just n })))
1570          Supported
1571   , Flag "fno-liberate-case-threshold"
1572          (NoArg (upd (\dfs -> dfs{ liberateCaseThreshold = Nothing })))
1573          Supported
1574
1575   , Flag "frule-check"
1576          (SepArg (\s -> upd (\dfs -> dfs{ ruleCheck = Just s })))
1577          Supported
1578   , Flag "fcontext-stack"
1579          (IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
1580          Supported
1581
1582   , Flag "fstrictness-before"
1583          (IntSuffix (\n -> upd (\dfs -> dfs{ strictnessBefore = n : strictnessBefore dfs })))
1584          Supported
1585
1586         ------ Profiling ----------------------------------------------------
1587
1588   -- XXX Should the -f* flags be deprecated?
1589   -- They don't seem to be documented
1590   , Flag "fauto-sccs-on-all-toplevs"
1591          (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1592          Supported
1593   , Flag "auto-all"
1594          (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1595          Supported
1596   , Flag "no-auto-all"
1597          (NoArg (unSetDynFlag Opt_AutoSccsOnAllToplevs))
1598          Supported
1599   , Flag "fauto-sccs-on-exported-toplevs"
1600          (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1601          Supported
1602   , Flag "auto"
1603          (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1604          Supported
1605   , Flag "no-auto"
1606          (NoArg (unSetDynFlag Opt_AutoSccsOnExportedToplevs))
1607          Supported
1608   , Flag "fauto-sccs-on-individual-cafs"
1609          (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1610          Supported
1611   , Flag "caf-all"
1612          (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1613          Supported
1614   , Flag "no-caf-all"
1615          (NoArg (unSetDynFlag Opt_AutoSccsOnIndividualCafs))
1616          Supported
1617
1618         ------ DPH flags ----------------------------------------------------
1619
1620   , Flag "fdph-seq"
1621          (NoArg (setDPHBackend DPHSeq))
1622          Supported
1623   , Flag "fdph-par"
1624          (NoArg (setDPHBackend DPHPar))
1625          Supported
1626   , Flag "fdph-this"
1627          (NoArg (setDPHBackend DPHThis))
1628          Supported
1629
1630         ------ Compiler flags -----------------------------------------------
1631
1632   , Flag "fasm"             (NoArg (setObjTarget HscAsm)) Supported
1633   , Flag "fvia-c"           (NoArg (setObjTarget HscC)) Supported
1634   , Flag "fvia-C"           (NoArg (setObjTarget HscC)) Supported
1635
1636   , Flag "fno-code"         (NoArg (setTarget HscNothing)) Supported
1637   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted)) Supported
1638   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget)) Supported
1639
1640   , Flag "fglasgow-exts"    (NoArg (mapM_ setDynFlag   glasgowExtsFlags))
1641          Supported
1642   , Flag "fno-glasgow-exts" (NoArg (mapM_ unSetDynFlag glasgowExtsFlags))
1643          Supported
1644  ]
1645  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
1646  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
1647  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
1648  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
1649
1650 package_flags :: [Flag DynP]
1651 package_flags = [
1652         ------- Packages ----------------------------------------------------
1653     Flag "package-conf"   (HasArg extraPkgConf_) Supported
1654   , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
1655          Supported
1656   , Flag "package-name"   (HasArg (upd . setPackageName)) Supported
1657   , Flag "package-id"     (HasArg exposePackageId) Supported
1658   , Flag "package"        (HasArg exposePackage) Supported
1659   , Flag "hide-package"   (HasArg hidePackage) Supported
1660   , Flag "hide-all-packages" (NoArg (setDynFlag Opt_HideAllPackages))
1661          Supported
1662   , Flag "ignore-package" (HasArg ignorePackage)
1663          Supported
1664   , Flag "syslib"         (HasArg exposePackage)
1665          (Deprecated "Use -package instead")
1666   ]
1667
1668 mkFlag :: Bool                  -- ^ True <=> it should be turned on
1669        -> String                -- ^ The flag prefix
1670        -> (DynFlag -> DynP ())
1671        -> (String, DynFlag, Bool -> Deprecated)
1672        -> Flag DynP
1673 mkFlag turnOn flagPrefix f (name, dynflag, deprecated)
1674     = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
1675
1676 deprecatedForLanguage :: String -> Bool -> Deprecated
1677 deprecatedForLanguage lang turn_on
1678     = Deprecated ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead")
1679     where 
1680       flag | turn_on    = lang
1681            | otherwise = "No"++lang
1682
1683 useInstead :: String -> Bool -> Deprecated
1684 useInstead flag turn_on
1685   = Deprecated ("Use -f" ++ no ++ flag ++ " instead")
1686   where
1687     no = if turn_on then "" else "no-"
1688
1689 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1690 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
1691 fFlags = [
1692   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
1693   ( "warn-dodgy-exports",               Opt_WarnDodgyExports, const Supported ),
1694   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, const Supported ),
1695   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, const Supported ),
1696   ( "warn-hi-shadowing",                Opt_WarnHiShadows, const Supported ),
1697   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, const Supported ),
1698   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, const Supported ),
1699   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, const Supported ),
1700   ( "warn-missing-fields",              Opt_WarnMissingFields, const Supported ),
1701   ( "warn-missing-methods",             Opt_WarnMissingMethods, const Supported ),
1702   ( "warn-missing-signatures",          Opt_WarnMissingSigs, const Supported ),
1703   ( "warn-name-shadowing",              Opt_WarnNameShadowing, const Supported ),
1704   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns, const Supported ),
1705   ( "warn-simple-patterns",             Opt_WarnSimplePatterns, const Supported ),
1706   ( "warn-type-defaults",               Opt_WarnTypeDefaults, const Supported ),
1707   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism, const Supported ),
1708   ( "warn-unused-binds",                Opt_WarnUnusedBinds, const Supported ),
1709   ( "warn-unused-imports",              Opt_WarnUnusedImports, const Supported ),
1710   ( "warn-unused-matches",              Opt_WarnUnusedMatches, const Supported ),
1711   ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, const Supported ),
1712   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, const Supported ),
1713   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, const Supported ),
1714   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
1715   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
1716   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, const Supported ),
1717   ( "warn-lazy-unlifted-bindings",      Opt_WarnLazyUnliftedBindings,
1718     const $ Deprecated "lazy unlifted bindings will be an error in GHC 6.14, and this flag will no longer exist"),
1719   ( "warn-unused-do-bind",              Opt_WarnUnusedDoBind, const Supported ),
1720   ( "warn-wrong-do-bind",               Opt_WarnWrongDoBind, const Supported ),
1721   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
1722   ( "strictness",                       Opt_Strictness, const Supported ),
1723   ( "specialise",                       Opt_Specialise, const Supported ),
1724   ( "float-in",                         Opt_FloatIn, const Supported ),
1725   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
1726   ( "full-laziness",                    Opt_FullLaziness, const Supported ),
1727   ( "liberate-case",                    Opt_LiberateCase, const Supported ),
1728   ( "spec-constr",                      Opt_SpecConstr, const Supported ),
1729   ( "cse",                              Opt_CSE, const Supported ),
1730   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas, const Supported ),
1731   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas, const Supported ),
1732   ( "expose-all-unfoldings",            Opt_ExposeAllUnfoldings, const Supported ),
1733   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion, const Supported ),
1734   ( "ignore-asserts",                   Opt_IgnoreAsserts, const Supported ),
1735   ( "do-eta-reduction",                 Opt_DoEtaReduction, const Supported ),
1736   ( "case-merge",                       Opt_CaseMerge, const Supported ),
1737   ( "unbox-strict-fields",              Opt_UnboxStrictFields, const Supported ),
1738   ( "method-sharing",                   Opt_MethodSharing, const Supported ),
1739   ( "dicts-cheap",                      Opt_DictsCheap, const Supported ),
1740   ( "excess-precision",                 Opt_ExcessPrecision, const Supported ),
1741   ( "eager-blackholing",                Opt_EagerBlackHoling, const Supported ),
1742   ( "asm-mangling",                     Opt_DoAsmMangling, const Supported ),
1743   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
1744   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
1745   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
1746   ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
1747   ( "enable-rewrite-rules",             Opt_EnableRewriteRules, const Supported ),
1748   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
1749   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
1750   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
1751   ( "print-bind-contents",              Opt_PrintBindContents, const Supported ),
1752   ( "run-cps",                          Opt_RunCPS, const Supported ),
1753   ( "run-cpsz",                         Opt_RunCPSZ, const Supported ),
1754   ( "new-codegen",                      Opt_TryNewCodeGen, const Supported ),
1755   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, const Supported ),
1756   ( "vectorise",                        Opt_Vectorise, const Supported ),
1757   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
1758   ( "regs-iterative",                   Opt_RegsIterative, const Supported ),
1759   ( "th",                               Opt_TemplateHaskell,
1760     deprecatedForLanguage "TemplateHaskell" ),
1761   ( "fi",                               Opt_ForeignFunctionInterface,
1762     deprecatedForLanguage "ForeignFunctionInterface" ),
1763   ( "ffi",                              Opt_ForeignFunctionInterface,
1764     deprecatedForLanguage "ForeignFunctionInterface" ),
1765   ( "arrows",                           Opt_Arrows,
1766     deprecatedForLanguage "Arrows" ),
1767   ( "generics",                         Opt_Generics,
1768     deprecatedForLanguage "Generics" ),
1769   ( "implicit-prelude",                 Opt_ImplicitPrelude,
1770     deprecatedForLanguage "ImplicitPrelude" ),
1771   ( "bang-patterns",                    Opt_BangPatterns,
1772     deprecatedForLanguage "BangPatterns" ),
1773   ( "monomorphism-restriction",         Opt_MonomorphismRestriction,
1774     deprecatedForLanguage "MonomorphismRestriction" ),
1775   ( "mono-pat-binds",                   Opt_MonoPatBinds,
1776     deprecatedForLanguage "MonoPatBinds" ),
1777   ( "extended-default-rules",           Opt_ExtendedDefaultRules,
1778     deprecatedForLanguage "ExtendedDefaultRules" ),
1779   ( "implicit-params",                  Opt_ImplicitParams,
1780     deprecatedForLanguage "ImplicitParams" ),
1781   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
1782     deprecatedForLanguage "ScopedTypeVariables" ),
1783   ( "parr",                             Opt_PArr,
1784     deprecatedForLanguage "PArr" ),
1785   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
1786     deprecatedForLanguage "OverlappingInstances" ),
1787   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
1788     deprecatedForLanguage "UndecidableInstances" ),
1789   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
1790     deprecatedForLanguage "IncoherentInstances" ),
1791   ( "gen-manifest",                     Opt_GenManifest, const Supported ),
1792   ( "embed-manifest",                   Opt_EmbedManifest, const Supported ),
1793   ( "ext-core",                         Opt_EmitExternalCore, const Supported ),
1794   ( "shared-implib",                    Opt_SharedImplib, const Supported ),
1795   ( "building-cabal-package",           Opt_BuildingCabalPackage, const Supported ),
1796   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
1797   ]
1798
1799 supportedLanguages :: [String]
1800 supportedLanguages = [ name | (name, _, _) <- xFlags ]
1801
1802 -- This may contain duplicates
1803 languageOptions :: [DynFlag]
1804 languageOptions = [ dynFlag | (_, dynFlag, _) <- xFlags ]
1805
1806 -- | These -X<blah> flags can all be reversed with -XNo<blah>
1807 xFlags :: [(String, DynFlag, Bool -> Deprecated)]
1808 xFlags = [
1809   ( "CPP",                              Opt_Cpp, const Supported ),
1810   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
1811   ( "TupleSections",                    Opt_TupleSections, const Supported ),
1812   ( "PatternGuards",                    Opt_PatternGuards, const Supported ),
1813   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, const Supported ),
1814   ( "MagicHash",                        Opt_MagicHash, const Supported ),
1815   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
1816   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
1817   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
1818   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
1819   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
1820   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
1821   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, const Supported ),
1822   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, const Supported ),
1823   ( "GHCForeignImportPrim",             Opt_GHCForeignImportPrim, const Supported ),
1824   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, const Supported ),
1825   ( "Rank2Types",                       Opt_Rank2Types, const Supported ),
1826   ( "RankNTypes",                       Opt_RankNTypes, const Supported ),
1827   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, 
1828         const $ Deprecated "impredicative polymorphism will be simplified or removed in GHC 6.14" ),
1829   ( "TypeOperators",                    Opt_TypeOperators, const Supported ),
1830   ( "RecursiveDo",                      Opt_RecursiveDo,
1831     deprecatedForLanguage "DoRec"),
1832   ( "DoRec",                            Opt_DoRec, const Supported ),
1833   ( "Arrows",                           Opt_Arrows, const Supported ),
1834   ( "PArr",                             Opt_PArr, const Supported ),
1835   ( "TemplateHaskell",                  Opt_TemplateHaskell, const Supported ),
1836   ( "QuasiQuotes",                      Opt_QuasiQuotes, const Supported ),
1837   ( "Generics",                         Opt_Generics, const Supported ),
1838   -- On by default:
1839   ( "ImplicitPrelude",                  Opt_ImplicitPrelude, const Supported ),
1840   ( "RecordWildCards",                  Opt_RecordWildCards, const Supported ),
1841   ( "NamedFieldPuns",                   Opt_RecordPuns, const Supported ),
1842   ( "RecordPuns",                       Opt_RecordPuns,
1843     deprecatedForLanguage "NamedFieldPuns" ),
1844   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, const Supported ),
1845   ( "OverloadedStrings",                Opt_OverloadedStrings, const Supported ),
1846   ( "GADTs",                            Opt_GADTs, const Supported ),
1847   ( "ViewPatterns",                     Opt_ViewPatterns, const Supported ),
1848   ( "TypeFamilies",                     Opt_TypeFamilies, const Supported ),
1849   ( "BangPatterns",                     Opt_BangPatterns, const Supported ),
1850   -- On by default:
1851   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, const Supported ),
1852   -- On by default:
1853   ( "NPlusKPatterns",                   Opt_NPlusKPatterns, const Supported ),
1854   -- On by default (which is not strictly H98):
1855   ( "MonoPatBinds",                     Opt_MonoPatBinds, const Supported ),
1856   ( "ExplicitForAll",                   Opt_ExplicitForAll, const Supported ),
1857   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, const Supported ),
1858   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, const Supported ),
1859   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
1860   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
1861   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
1862   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
1863
1864   ( "PatternSignatures",                Opt_ScopedTypeVariables, 
1865     deprecatedForLanguage "ScopedTypeVariables" ),
1866
1867   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
1868   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
1869   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
1870   ( "DeriveFunctor",                    Opt_DeriveFunctor, const Supported ),
1871   ( "DeriveTraversable",                Opt_DeriveTraversable, const Supported ),
1872   ( "DeriveFoldable",                   Opt_DeriveFoldable, const Supported ),
1873   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, const Supported ),
1874   ( "FlexibleContexts",                 Opt_FlexibleContexts, const Supported ),
1875   ( "FlexibleInstances",                Opt_FlexibleInstances, const Supported ),
1876   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods, const Supported ),
1877   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses, const Supported ),
1878   ( "FunctionalDependencies",           Opt_FunctionalDependencies, const Supported ),
1879   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, const Supported ),
1880   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
1881   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
1882   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
1883   ( "PackageImports",                   Opt_PackageImports, const Supported ),
1884   ( "NewQualifiedOperators",            Opt_NewQualifiedOperators, const Supported )
1885   ]
1886
1887 impliedFlags :: [(DynFlag, DynFlag)]
1888 impliedFlags
1889   = [ (Opt_RankNTypes,                Opt_ExplicitForAll)
1890     , (Opt_Rank2Types,                Opt_ExplicitForAll)
1891     , (Opt_ScopedTypeVariables,       Opt_ExplicitForAll)
1892     , (Opt_LiberalTypeSynonyms,       Opt_ExplicitForAll)
1893     , (Opt_ExistentialQuantification, Opt_ExplicitForAll)
1894     , (Opt_PolymorphicComponents,     Opt_ExplicitForAll)
1895
1896     , (Opt_GADTs,               Opt_RelaxedPolyRec)  -- We want type-sig variables to
1897                                                      --      be completely rigid for GADTs
1898
1899     , (Opt_TypeFamilies,        Opt_RelaxedPolyRec)  -- Trac #2944 gives a nice example
1900     , (Opt_TypeFamilies,        Opt_KindSignatures)  -- Type families use kind signatures
1901                                                      -- all over the place
1902
1903     , (Opt_ScopedTypeVariables, Opt_RelaxedPolyRec)  -- Ditto for scoped type variables; see
1904                                                      --      Note [Scoped tyvars] in TcBinds
1905     , (Opt_ImpredicativeTypes,  Opt_RankNTypes)
1906
1907         -- Record wild-cards implies field disambiguation
1908         -- Otherwise if you write (C {..}) you may well get
1909         -- stuff like " 'a' not in scope ", which is a bit silly
1910         -- if the compiler has just filled in field 'a' of constructor 'C'
1911     , (Opt_RecordWildCards,     Opt_DisambiguateRecordFields)
1912   ]
1913
1914 glasgowExtsFlags :: [DynFlag]
1915 glasgowExtsFlags = [
1916              Opt_PrintExplicitForalls
1917            , Opt_ForeignFunctionInterface
1918            , Opt_UnliftedFFITypes
1919            , Opt_GADTs
1920            , Opt_ImplicitParams
1921            , Opt_ScopedTypeVariables
1922            , Opt_UnboxedTuples
1923            , Opt_TypeSynonymInstances
1924            , Opt_StandaloneDeriving
1925            , Opt_DeriveDataTypeable
1926            , Opt_DeriveFunctor
1927            , Opt_DeriveFoldable
1928            , Opt_DeriveTraversable
1929            , Opt_FlexibleContexts
1930            , Opt_FlexibleInstances
1931            , Opt_ConstrainedClassMethods
1932            , Opt_MultiParamTypeClasses
1933            , Opt_FunctionalDependencies
1934            , Opt_MagicHash
1935            , Opt_PolymorphicComponents
1936            , Opt_ExistentialQuantification
1937            , Opt_UnicodeSyntax
1938            , Opt_PostfixOperators
1939            , Opt_PatternGuards
1940            , Opt_LiberalTypeSynonyms
1941            , Opt_RankNTypes
1942            , Opt_TypeOperators
1943            , Opt_DoRec
1944            , Opt_ParallelListComp
1945            , Opt_EmptyDataDecls
1946            , Opt_KindSignatures
1947            , Opt_GeneralizedNewtypeDeriving
1948            , Opt_TypeFamilies ]
1949
1950 -- -----------------------------------------------------------------------------
1951 -- Parsing the dynamic flags.
1952
1953 -- | Parse dynamic flags from a list of command line arguments.  Returns the
1954 -- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
1955 -- Throws a 'UsageError' if errors occurred during parsing (such as unknown
1956 -- flags or missing arguments).
1957 parseDynamicFlags :: Monad m =>
1958                      DynFlags -> [Located String]
1959                   -> m (DynFlags, [Located String], [Located String])
1960                      -- ^ Updated 'DynFlags', left-over arguments, and
1961                      -- list of warnings.
1962 parseDynamicFlags dflags args = parseDynamicFlags_ dflags args True
1963
1964 -- | Like 'parseDynamicFlags' but does not allow the package flags (-package,
1965 -- -hide-package, -ignore-package, -hide-all-packages, -package-conf).
1966 parseDynamicNoPackageFlags :: Monad m =>
1967                      DynFlags -> [Located String]
1968                   -> m (DynFlags, [Located String], [Located String])
1969                      -- ^ Updated 'DynFlags', left-over arguments, and
1970                      -- list of warnings.
1971 parseDynamicNoPackageFlags dflags args = parseDynamicFlags_ dflags args False
1972
1973 parseDynamicFlags_ :: Monad m =>
1974                       DynFlags -> [Located String] -> Bool
1975                   -> m (DynFlags, [Located String], [Located String])
1976 parseDynamicFlags_ dflags0 args pkg_flags = do
1977   -- XXX Legacy support code
1978   -- We used to accept things like
1979   --     optdep-f  -optdepdepend
1980   --     optdep-f  -optdep depend
1981   --     optdep -f -optdepdepend
1982   --     optdep -f -optdep depend
1983   -- but the spaces trip up proper argument handling. So get rid of them.
1984   let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs
1985       f (x : xs) = x : f xs
1986       f xs = xs
1987       args' = f args
1988
1989       -- Note: -ignore-package (package_flags) must precede -i* (dynamic_flags)
1990       flag_spec | pkg_flags = package_flags ++ dynamic_flags
1991                 | otherwise = dynamic_flags
1992
1993   let ((leftover, errs, warns), dflags1)
1994           = runCmdLine (processArgs flag_spec args') dflags0
1995   when (not (null errs)) $ ghcError $ errorsToGhcException errs
1996
1997   -- Cannot use -fPIC with registerised -fvia-C, because the mangler
1998   -- isn't up to the job.  We know that if hscTarget == HscC, then the
1999   -- user has explicitly used -fvia-C, because -fasm is the default,
2000   -- unless there is no NCG on this platform.  The latter case is
2001   -- checked when the -fPIC flag is parsed.
2002   --
2003   let (pic_warns, dflags2) =
2004         if opt_PIC && hscTarget dflags1 == HscC && cGhcUnregisterised == "NO"
2005           then ([L noSrcSpan $ "Warning: -fvia-C is incompatible with -fPIC; ignoring -fvia-C"],
2006                 dflags1{ hscTarget = HscAsm })
2007           else ([], dflags1)
2008
2009   return (dflags2, leftover, pic_warns ++ warns)
2010
2011 type DynP = CmdLineP DynFlags
2012
2013 upd :: (DynFlags -> DynFlags) -> DynP ()
2014 upd f = do
2015    dfs <- getCmdLineState
2016    putCmdLineState $! (f dfs)
2017
2018 --------------------------
2019 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
2020 setDynFlag f = do { upd (\dfs -> dopt_set dfs f)
2021                   ; mapM_ setDynFlag deps }
2022   where
2023     deps = [ d | (f', d) <- impliedFlags, f' == f ]
2024         -- When you set f, set the ones it implies
2025         -- NB: use setDynFlag recursively, in case the implied flags
2026         --     implies further flags
2027         -- When you un-set f, however, we don't un-set the things it implies
2028         --      (except for -fno-glasgow-exts, which is treated specially)
2029
2030 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
2031
2032 --------------------------
2033 setDumpFlag :: DynFlag -> OptKind DynP
2034 setDumpFlag dump_flag
2035   = NoArg (do { setDynFlag dump_flag
2036               ; when want_recomp forceRecompile })
2037   where
2038         -- Certain dumpy-things are really interested in what's going
2039         -- on during recompilation checking, so in those cases we
2040         -- don't want to turn it off.
2041     want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
2042                                        Opt_D_dump_hi_diffs]
2043
2044 forceRecompile :: DynP ()
2045 -- Whenver we -ddump, force recompilation (by switching off the 
2046 -- recompilation checker), else you don't see the dump! However, 
2047 -- don't switch it off in --make mode, else *everything* gets
2048 -- recompiled which probably isn't what you want
2049 forceRecompile = do { dfs <- getCmdLineState
2050                     ; when (force_recomp dfs) (setDynFlag Opt_ForceRecomp) }
2051         where
2052           force_recomp dfs = isOneShot (ghcMode dfs)
2053
2054 setVerboseCore2Core :: DynP ()
2055 setVerboseCore2Core = do setDynFlag Opt_D_verbose_core2core 
2056                          forceRecompile
2057                          upd (\s -> s { shouldDumpSimplPhase = const True })
2058
2059 setDumpSimplPhases :: String -> DynP ()
2060 setDumpSimplPhases s = do forceRecompile
2061                           upd (\s -> s { shouldDumpSimplPhase = spec })
2062   where
2063     spec :: SimplifierMode -> Bool
2064     spec = join (||)
2065          . map (join (&&) . map match . split ':')
2066          . split ','
2067          $ case s of
2068              '=' : s' -> s'
2069              _        -> s
2070
2071     join :: (Bool -> Bool -> Bool)
2072          -> [SimplifierMode -> Bool]
2073          -> SimplifierMode -> Bool
2074     join _  [] = const True
2075     join op ss = foldr1 (\f g x -> f x `op` g x) ss
2076
2077     match :: String -> SimplifierMode -> Bool
2078     match "" = const True
2079     match s  = case reads s of
2080                 [(n,"")] -> phase_num  n
2081                 _        -> phase_name s
2082
2083     phase_num :: Int -> SimplifierMode -> Bool
2084     phase_num n (SimplPhase k _) = n == k
2085     phase_num _ _                = False
2086
2087     phase_name :: String -> SimplifierMode -> Bool
2088     phase_name s (SimplGently {})               = s == "gentle"
2089     phase_name s (SimplPhase { sm_names = ss }) = s `elem` ss
2090
2091 setVerbosity :: Maybe Int -> DynP ()
2092 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
2093
2094 addCmdlineHCInclude :: String -> DynP ()
2095 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
2096
2097 extraPkgConf_ :: FilePath -> DynP ()
2098 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
2099
2100 exposePackage, exposePackageId, hidePackage, ignorePackage :: String -> DynP ()
2101 exposePackage p =
2102   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
2103 exposePackageId p =
2104   upd (\s -> s{ packageFlags = ExposePackageId p : packageFlags s })
2105 hidePackage p =
2106   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
2107 ignorePackage p =
2108   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
2109
2110 setPackageName :: String -> DynFlags -> DynFlags
2111 setPackageName p s =  s{ thisPackage = stringToPackageId p }
2112
2113 -- If we're linking a binary, then only targets that produce object
2114 -- code are allowed (requests for other target types are ignored).
2115 setTarget :: HscTarget -> DynP ()
2116 setTarget l = upd set
2117   where
2118    set dfs
2119      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
2120      | otherwise = dfs
2121
2122 -- Changes the target only if we're compiling object code.  This is
2123 -- used by -fasm and -fvia-C, which switch from one to the other, but
2124 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
2125 -- can be safely used in an OPTIONS_GHC pragma.
2126 setObjTarget :: HscTarget -> DynP ()
2127 setObjTarget l = upd set
2128   where
2129    set dfs
2130      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
2131      | otherwise = dfs
2132
2133 setOptLevel :: Int -> DynFlags -> DynFlags
2134 setOptLevel n dflags
2135    | hscTarget dflags == HscInterpreted && n > 0
2136         = dflags
2137             -- not in IO any more, oh well:
2138             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
2139    | otherwise
2140         = updOptLevel n dflags
2141
2142
2143 -- -Odph is equivalent to
2144 --
2145 --    -O2                               optimise as much as possible
2146 --    -fno-method-sharing               sharing specialisation defeats fusion
2147 --                                      sometimes
2148 --    -fdicts-cheap                     always inline dictionaries
2149 --    -fmax-simplifier-iterations20     this is necessary sometimes
2150 --    -fsimplifier-phases=3             we use an additional simplifier phase
2151 --                                      for fusion
2152 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
2153 --    -fno-spec-constr-count            SpecConstr as much as possible
2154 --    -finline-enough-args              hack to prevent excessive inlining
2155 --
2156 setDPHOpt :: DynFlags -> DynFlags
2157 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
2158                                          , simplPhases         = 3
2159                                          , specConstrThreshold = Nothing
2160                                          , specConstrCount     = Nothing
2161                                          })
2162                    `dopt_set`   Opt_DictsCheap
2163                    `dopt_unset` Opt_MethodSharing
2164
2165 data DPHBackend = DPHPar
2166                 | DPHSeq
2167                 | DPHThis
2168         deriving(Eq, Ord, Enum, Show)
2169
2170 setDPHBackend :: DPHBackend -> DynP ()
2171 setDPHBackend backend 
2172   = do
2173       upd $ \dflags -> dflags { dphBackend = backend }
2174       mapM_ exposePackage (dph_packages backend)
2175   where
2176     dph_packages DPHThis = []
2177     dph_packages DPHPar  = ["dph-prim-par", "dph-par"]
2178     dph_packages DPHSeq  = ["dph-prim-seq", "dph-seq"]
2179
2180 dphPackage :: DynFlags -> PackageId
2181 dphPackage dflags = case dphBackend dflags of
2182                       DPHPar  -> dphParPackageId
2183                       DPHSeq  -> dphSeqPackageId
2184                       DPHThis -> thisPackage dflags
2185
2186 setMainIs :: String -> DynP ()
2187 setMainIs arg
2188   | not (null main_fn) && isLower (head main_fn)
2189      -- The arg looked like "Foo.Bar.baz"
2190   = upd $ \d -> d{ mainFunIs = Just main_fn,
2191                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
2192
2193   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
2194   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
2195
2196   | otherwise                   -- The arg looked like "baz"
2197   = upd $ \d -> d{ mainFunIs = Just arg }
2198   where
2199     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
2200
2201 -----------------------------------------------------------------------------
2202 -- Paths & Libraries
2203
2204 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
2205
2206 -- -i on its own deletes the import paths
2207 addImportPath "" = upd (\s -> s{importPaths = []})
2208 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
2209
2210
2211 addLibraryPath p =
2212   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
2213
2214 addIncludePath p =
2215   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
2216
2217 addFrameworkPath p =
2218   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
2219
2220 #ifndef mingw32_TARGET_OS
2221 split_marker :: Char
2222 split_marker = ':'   -- not configurable (ToDo)
2223 #endif
2224
2225 splitPathList :: String -> [String]
2226 splitPathList s = filter notNull (splitUp s)
2227                 -- empty paths are ignored: there might be a trailing
2228                 -- ':' in the initial list, for example.  Empty paths can
2229                 -- cause confusion when they are translated into -I options
2230                 -- for passing to gcc.
2231   where
2232 #ifndef mingw32_TARGET_OS
2233     splitUp xs = split split_marker xs
2234 #else
2235      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
2236      --
2237      -- That is, if "foo:bar:baz" is used, this interpreted as
2238      -- consisting of three entries, 'foo', 'bar', 'baz'.
2239      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
2240      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
2241      --
2242      -- Notice that no attempt is made to fully replace the 'standard'
2243      -- split marker ':' with the Windows / DOS one, ';'. The reason being
2244      -- that this will cause too much breakage for users & ':' will
2245      -- work fine even with DOS paths, if you're not insisting on being silly.
2246      -- So, use either.
2247     splitUp []             = []
2248     splitUp (x:':':div:xs) | div `elem` dir_markers
2249                            = ((x:':':div:p): splitUp rs)
2250                            where
2251                               (p,rs) = findNextPath xs
2252           -- we used to check for existence of the path here, but that
2253           -- required the IO monad to be threaded through the command-line
2254           -- parser which is quite inconvenient.  The
2255     splitUp xs = cons p (splitUp rs)
2256                where
2257                  (p,rs) = findNextPath xs
2258
2259                  cons "" xs = xs
2260                  cons x  xs = x:xs
2261
2262     -- will be called either when we've consumed nought or the
2263     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
2264     -- finding the next split marker.
2265     findNextPath xs =
2266         case break (`elem` split_markers) xs of
2267            (p, _:ds) -> (p, ds)
2268            (p, xs)   -> (p, xs)
2269
2270     split_markers :: [Char]
2271     split_markers = [':', ';']
2272
2273     dir_markers :: [Char]
2274     dir_markers = ['/', '\\']
2275 #endif
2276
2277 -- -----------------------------------------------------------------------------
2278 -- tmpDir, where we store temporary files.
2279
2280 setTmpDir :: FilePath -> DynFlags -> DynFlags
2281 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
2282   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
2283   -- seem necessary now --SDM 7/2/2008
2284
2285 -----------------------------------------------------------------------------
2286 -- Hpc stuff
2287
2288 setOptHpcDir :: String -> DynP ()
2289 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
2290
2291 -----------------------------------------------------------------------------
2292 -- Via-C compilation stuff
2293
2294 -- There are some options that we need to pass to gcc when compiling
2295 -- Haskell code via C, but are only supported by recent versions of
2296 -- gcc.  The configure script decides which of these options we need,
2297 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
2298 -- read before each via-C compilation.  The advantage of having these
2299 -- in a separate file is that the file can be created at install-time
2300 -- depending on the available gcc version, and even re-generated  later
2301 -- if gcc is upgraded.
2302 --
2303 -- The options below are not dependent on the version of gcc, only the
2304 -- platform.
2305
2306 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
2307                               [String]) -- for registerised HC compilations
2308 machdepCCOpts _dflags
2309 #if alpha_TARGET_ARCH
2310         =       ( ["-w", "-mieee"
2311 #ifdef HAVE_THREADED_RTS_SUPPORT
2312                     , "-D_REENTRANT"
2313 #endif
2314                    ], [] )
2315         -- For now, to suppress the gcc warning "call-clobbered
2316         -- register used for global register variable", we simply
2317         -- disable all warnings altogether using the -w flag. Oh well.
2318
2319 #elif hppa_TARGET_ARCH
2320         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
2321         -- (very nice, but too bad the HP /usr/include files don't agree.)
2322         = ( ["-D_HPUX_SOURCE"], [] )
2323
2324 #elif m68k_TARGET_ARCH
2325       -- -fno-defer-pop : for the .hc files, we want all the pushing/
2326       --    popping of args to routines to be explicit; if we let things
2327       --    be deferred 'til after an STGJUMP, imminent death is certain!
2328       --
2329       -- -fomit-frame-pointer : *don't*
2330       --     It's better to have a6 completely tied up being a frame pointer
2331       --     rather than let GCC pick random things to do with it.
2332       --     (If we want to steal a6, then we would try to do things
2333       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
2334         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
2335
2336 #elif i386_TARGET_ARCH
2337       -- -fno-defer-pop : basically the same game as for m68k
2338       --
2339       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
2340       --   the fp (%ebp) for our register maps.
2341         =  let n_regs = stolen_x86_regs _dflags
2342            in
2343                     ( 
2344 #if darwin_TARGET_OS
2345                       -- By default, gcc on OS X will generate SSE
2346                       -- instructions, which need things 16-byte aligned,
2347                       -- but we don't 16-byte align things. Thus drop
2348                       -- back to generic i686 compatibility. Trac #2983.
2349                       --
2350                       -- Since Snow Leopard (10.6), gcc defaults to x86_64.
2351                       ["-march=i686", "-m32"],
2352 #else
2353                       [ if opt_Static then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
2354                       ],
2355 #endif
2356                       [ "-fno-defer-pop",
2357                         "-fomit-frame-pointer",
2358                         -- we want -fno-builtin, because when gcc inlines
2359                         -- built-in functions like memcpy() it tends to
2360                         -- run out of registers, requiring -monly-n-regs
2361                         "-fno-builtin",
2362                         "-DSTOLEN_X86_REGS="++show n_regs ]
2363                     )
2364
2365 #elif ia64_TARGET_ARCH
2366         = ( [], ["-fomit-frame-pointer", "-G0"] )
2367
2368 #elif x86_64_TARGET_ARCH
2369         = (
2370 #if darwin_TARGET_OS
2371             ["-m64"],
2372 #else
2373             [],
2374 #endif
2375                 ["-fomit-frame-pointer",
2376                  "-fno-asynchronous-unwind-tables",
2377                         -- the unwind tables are unnecessary for HC code,
2378                         -- and get in the way of -split-objs.  Another option
2379                         -- would be to throw them away in the mangler, but this
2380                         -- is easier.
2381                  "-fno-builtin"
2382                         -- calling builtins like strlen() using the FFI can
2383                         -- cause gcc to run out of regs, so use the external
2384                         -- version.
2385                 ] )
2386
2387 #elif sparc_TARGET_ARCH
2388         = ( [], ["-w"] )
2389         -- For now, to suppress the gcc warning "call-clobbered
2390         -- register used for global register variable", we simply
2391         -- disable all warnings altogether using the -w flag. Oh well.
2392
2393 #elif powerpc_apple_darwin_TARGET
2394       -- -no-cpp-precomp:
2395       --     Disable Apple's precompiling preprocessor. It's a great thing
2396       --     for "normal" programs, but it doesn't support register variable
2397       --     declarations.
2398         = ( [], ["-no-cpp-precomp"] )
2399 #else
2400         = ( [], [] )
2401 #endif
2402
2403 picCCOpts :: DynFlags -> [String]
2404 picCCOpts _dflags
2405 #if darwin_TARGET_OS
2406       -- Apple prefers to do things the other way round.
2407       -- PIC is on by default.
2408       -- -mdynamic-no-pic:
2409       --     Turn off PIC code generation.
2410       -- -fno-common:
2411       --     Don't generate "common" symbols - these are unwanted
2412       --     in dynamic libraries.
2413
2414     | opt_PIC
2415         = ["-fno-common", "-U __PIC__","-D__PIC__"]
2416     | otherwise
2417         = ["-mdynamic-no-pic"]
2418 #elif mingw32_TARGET_OS
2419       -- no -fPIC for Windows
2420     | opt_PIC
2421         = ["-U __PIC__","-D__PIC__"]
2422     | otherwise
2423         = []
2424 #else
2425     | opt_PIC || not opt_Static
2426         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
2427     | otherwise
2428         = []
2429 #endif
2430
2431 -- -----------------------------------------------------------------------------
2432 -- Splitting
2433
2434 can_split :: Bool
2435 can_split = cSplitObjs == "YES"
2436
2437 -- -----------------------------------------------------------------------------
2438 -- Compiler Info
2439
2440 data Printable = String String
2441                | FromDynFlags (DynFlags -> String)
2442
2443 compilerInfo :: [(String, Printable)]
2444 compilerInfo = [("Project name",                String cProjectName),
2445                 ("Project version",             String cProjectVersion),
2446                 ("Booter version",              String cBooterVersion),
2447                 ("Stage",                       String cStage),
2448                 ("Have interpreter",            String cGhcWithInterpreter),
2449                 ("Object splitting",            String cSplitObjs),
2450                 ("Have native code generator",  String cGhcWithNativeCodeGen),
2451                 ("Support SMP",                 String cGhcWithSMP),
2452                 ("Unregisterised",              String cGhcUnregisterised),
2453                 ("Tables next to code",         String cGhcEnableTablesNextToCode),
2454                 ("Win32 DLLs",                  String cEnableWin32DLLs),
2455                 ("RTS ways",                    String cGhcRTSWays),
2456                 ("Leading underscore",          String cLeadingUnderscore),
2457                 ("Debug on",                    String (show debugIsOn)),
2458                 ("LibDir",                      FromDynFlags topDir)
2459                ]
2460