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