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