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