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