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