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