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