Separate flags -XDeriveFunctor, -XDeriveFoldable, -XDeriveTraversable
[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         getMainFun,
35         updOptLevel,
36         setTmpDir,
37         setPackageName,
38         doingTickyProfiling,
39
40         -- ** Parsing DynFlags
41         parseDynamicFlags,
42         parseDynamicNoPackageFlags,
43         allFlags,
44
45         supportedLanguages, languageOptions,
46
47         -- ** DynFlag C compiler options
48         machdepCCOpts, picCCOpts,
49
50         -- * Configuration of the core-to-core passes
51         CoreToDo(..),
52         SimplifierMode(..),
53         SimplifierSwitch(..),
54         FloatOutSwitches(..),
55         getCoreToDo,
56
57         -- * Configuration of the stg-to-stg passes
58         StgToDo(..),
59         getStgToDo,
60
61         -- * Compiler configuration suitable for display to the user
62         compilerInfo
63   ) where
64
65 #include "HsVersions.h"
66
67 #ifndef OMIT_NATIVE_CODEGEN
68 import Platform
69 #endif
70 import Module
71 import PackageConfig
72 import PrelNames        ( mAIN, main_RDR_Unqual )
73 import RdrName          ( RdrName, mkRdrUnqual )
74 import OccName          ( mkVarOccFS )
75 #if defined(i386_TARGET_ARCH) || (!defined(mingw32_TARGET_OS) && !defined(darwin_TARGET_OS))
76 import StaticFlags      ( opt_Static )
77 #endif
78 import StaticFlags      ( opt_PIC, WayName(..), v_Ways, v_Build_tag,
79                           v_RTS_Build_tag )
80 import {-# SOURCE #-} Packages (PackageState)
81 import DriverPhases     ( Phase(..), phaseInputExt )
82 import Config
83 import CmdLineParser
84 import Constants        ( mAX_CONTEXT_REDUCTION_DEPTH )
85 import Panic
86 import UniqFM           ( UniqFM )
87 import Util
88 import Maybes           ( orElse )
89 import SrcLoc
90 import FastString
91 import FiniteMap
92 import Outputable
93 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
94
95 import Data.IORef
96 import Control.Monad    ( when )
97
98 import Data.Char
99 import Data.List        ( intersperse )
100 import System.FilePath
101 import System.IO        ( stderr, hPutChar )
102
103 -- -----------------------------------------------------------------------------
104 -- DynFlags
105
106 -- | Enumerates the simple on-or-off dynamic flags
107 data DynFlag
108
109    -- debugging flags
110    = Opt_D_dump_cmm
111    | Opt_D_dump_cmmz
112    | Opt_D_dump_cmmz_pretty
113    | Opt_D_dump_cps_cmm
114    | Opt_D_dump_cvt_cmm
115    | Opt_D_dump_asm
116    | Opt_D_dump_asm_native
117    | Opt_D_dump_asm_liveness
118    | Opt_D_dump_asm_coalesce
119    | Opt_D_dump_asm_regalloc
120    | Opt_D_dump_asm_regalloc_stages
121    | Opt_D_dump_asm_conflicts
122    | Opt_D_dump_asm_stats
123    | Opt_D_dump_asm_expanded
124    | Opt_D_dump_cpranal
125    | Opt_D_dump_deriv
126    | Opt_D_dump_ds
127    | Opt_D_dump_flatC
128    | Opt_D_dump_foreign
129    | Opt_D_dump_inlinings
130    | Opt_D_dump_rule_firings
131    | Opt_D_dump_occur_anal
132    | Opt_D_dump_parsed
133    | Opt_D_dump_rn
134    | Opt_D_dump_simpl
135    | Opt_D_dump_simpl_iterations
136    | Opt_D_dump_simpl_phases
137    | Opt_D_dump_spec
138    | Opt_D_dump_prep
139    | Opt_D_dump_stg
140    | Opt_D_dump_stranal
141    | Opt_D_dump_tc
142    | Opt_D_dump_types
143    | Opt_D_dump_rules
144    | Opt_D_dump_cse
145    | Opt_D_dump_worker_wrapper
146    | Opt_D_dump_rn_trace
147    | Opt_D_dump_rn_stats
148    | Opt_D_dump_opt_cmm
149    | Opt_D_dump_simpl_stats
150    | Opt_D_dump_tc_trace
151    | Opt_D_dump_if_trace
152    | Opt_D_dump_splices
153    | Opt_D_dump_BCOs
154    | Opt_D_dump_vect
155    | Opt_D_dump_hpc
156    | Opt_D_dump_rtti
157    | Opt_D_source_stats
158    | Opt_D_verbose_core2core
159    | Opt_D_verbose_stg2stg
160    | Opt_D_dump_hi
161    | Opt_D_dump_hi_diffs
162    | Opt_D_dump_minimal_imports
163    | Opt_D_dump_mod_cycles
164    | Opt_D_dump_view_pattern_commoning
165    | Opt_D_faststring_stats
166    | Opt_DumpToFile                     -- ^ Append dump output to files instead of stdout.
167    | Opt_D_no_debug_output
168    | Opt_DoCoreLinting
169    | Opt_DoStgLinting
170    | Opt_DoCmmLinting
171    | Opt_DoAsmLinting
172
173    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
174    | Opt_WarnDuplicateExports
175    | Opt_WarnHiShadows
176    | Opt_WarnImplicitPrelude
177    | Opt_WarnIncompletePatterns
178    | Opt_WarnIncompletePatternsRecUpd
179    | Opt_WarnMissingFields
180    | Opt_WarnMissingMethods
181    | Opt_WarnMissingSigs
182    | Opt_WarnNameShadowing
183    | Opt_WarnOverlappingPatterns
184    | Opt_WarnSimplePatterns
185    | Opt_WarnTypeDefaults
186    | Opt_WarnMonomorphism
187    | Opt_WarnUnusedBinds
188    | Opt_WarnUnusedImports
189    | Opt_WarnUnusedMatches
190    | Opt_WarnWarningsDeprecations
191    | Opt_WarnDeprecatedFlags
192    | Opt_WarnDodgyImports
193    | Opt_WarnOrphans
194    | Opt_WarnTabs
195    | Opt_WarnUnrecognisedPragmas
196    | Opt_WarnDodgyForeignImports
197
198    -- language opts
199    | Opt_OverlappingInstances
200    | Opt_UndecidableInstances
201    | Opt_IncoherentInstances
202    | Opt_MonomorphismRestriction
203    | Opt_MonoPatBinds
204    | Opt_ExtendedDefaultRules           -- Use GHC's extended rules for defaulting
205    | Opt_ForeignFunctionInterface
206    | Opt_UnliftedFFITypes
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_WarnDodgyForeignImports
912       ]
913
914 minusWOpts :: [DynFlag]
915 minusWOpts
916     = standardWarnings ++
917       [ Opt_WarnUnusedBinds,
918         Opt_WarnUnusedMatches,
919         Opt_WarnUnusedImports,
920         Opt_WarnIncompletePatterns,
921         Opt_WarnDodgyImports
922       ]
923
924 minusWallOpts :: [DynFlag]
925 minusWallOpts
926     = minusWOpts ++
927       [ Opt_WarnTypeDefaults,
928         Opt_WarnNameShadowing,
929         Opt_WarnMissingSigs,
930         Opt_WarnHiShadows,
931         Opt_WarnOrphans
932       ]
933
934 -- minuswRemovesOpts should be every warning option
935 minuswRemovesOpts :: [DynFlag]
936 minuswRemovesOpts
937     = minusWallOpts ++
938       [Opt_WarnImplicitPrelude,
939        Opt_WarnIncompletePatternsRecUpd,
940        Opt_WarnSimplePatterns,
941        Opt_WarnMonomorphism,
942        Opt_WarnUnrecognisedPragmas,
943        Opt_WarnTabs
944       ]
945
946 -- -----------------------------------------------------------------------------
947 -- CoreToDo:  abstraction of core-to-core passes to run.
948
949 data CoreToDo           -- These are diff core-to-core passes,
950                         -- which may be invoked in any order,
951                         -- as many times as you like.
952
953   = CoreDoSimplify      -- The core-to-core simplifier.
954         SimplifierMode
955         [SimplifierSwitch]
956                         -- Each run of the simplifier can take a different
957                         -- set of simplifier-specific flags.
958   | CoreDoFloatInwards
959   | CoreDoFloatOutwards FloatOutSwitches
960   | CoreLiberateCase
961   | CoreDoPrintCore
962   | CoreDoStaticArgs
963   | CoreDoStrictness
964   | CoreDoWorkerWrapper
965   | CoreDoSpecialising
966   | CoreDoSpecConstr
967   | CoreDoOldStrictness
968   | CoreDoGlomBinds
969   | CoreCSE
970   | CoreDoRuleCheck Int{-CompilerPhase-} String -- Check for non-application of rules
971                                                 -- matching this string
972   | CoreDoVectorisation PackageId
973   | CoreDoNothing                -- Useful when building up
974   | CoreDoPasses [CoreToDo]      -- lists of these things
975
976
977 data SimplifierMode             -- See comments in SimplMonad
978   = SimplGently
979   | SimplPhase Int [String]
980
981 instance Outputable SimplifierMode where
982     ppr SimplGently       = ptext (sLit "gentle")
983     ppr (SimplPhase n ss) = int n <+> brackets (text (concat $ intersperse "," ss))
984
985
986 data SimplifierSwitch
987   = MaxSimplifierIterations Int
988   | NoCaseOfCase
989
990
991 data FloatOutSwitches = FloatOutSwitches {
992         floatOutLambdas :: Bool,     -- ^ True <=> float lambdas to top level
993         floatOutConstants :: Bool    -- ^ True <=> float constants to top level,
994                                      --            even if they do not escape a lambda
995     }
996
997 instance Outputable FloatOutSwitches where
998     ppr = pprFloatOutSwitches
999
1000 pprFloatOutSwitches :: FloatOutSwitches -> SDoc
1001 pprFloatOutSwitches sw = pp_not (floatOutLambdas sw) <+> text "lambdas" <> comma
1002                      <+> pp_not (floatOutConstants sw) <+> text "constants"
1003   where
1004     pp_not True  = empty
1005     pp_not False = text "not"
1006
1007 -- | Switches that specify the minimum amount of floating out
1008 -- gentleFloatOutSwitches :: FloatOutSwitches
1009 -- gentleFloatOutSwitches = FloatOutSwitches False False
1010
1011 -- | Switches that do not specify floating out of lambdas, just of constants
1012 constantsOnlyFloatOutSwitches :: FloatOutSwitches
1013 constantsOnlyFloatOutSwitches = FloatOutSwitches False True
1014
1015
1016 -- The core-to-core pass ordering is derived from the DynFlags:
1017 runWhen :: Bool -> CoreToDo -> CoreToDo
1018 runWhen True  do_this = do_this
1019 runWhen False _       = CoreDoNothing
1020
1021 runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo
1022 runMaybe (Just x) f = f x
1023 runMaybe Nothing  _ = CoreDoNothing
1024
1025 getCoreToDo :: DynFlags -> [CoreToDo]
1026 getCoreToDo dflags
1027   | Just todo <- coreToDo dflags = todo -- set explicitly by user
1028   | otherwise = core_todo
1029   where
1030     opt_level     = optLevel dflags
1031     phases        = simplPhases dflags
1032     max_iter      = maxSimplIterations dflags
1033     strictness    = dopt Opt_Strictness dflags
1034     full_laziness = dopt Opt_FullLaziness dflags
1035     cse           = dopt Opt_CSE dflags
1036     spec_constr   = dopt Opt_SpecConstr dflags
1037     liberate_case = dopt Opt_LiberateCase dflags
1038     rule_check    = ruleCheck dflags
1039     static_args   = dopt Opt_StaticArgumentTransformation dflags
1040
1041     maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase)
1042
1043     simpl_phase phase names iter
1044       = CoreDoPasses
1045           [ CoreDoSimplify (SimplPhase phase names) [
1046               MaxSimplifierIterations iter
1047             ],
1048             maybe_rule_check phase
1049           ]
1050
1051     vectorisation
1052       = runWhen (dopt Opt_Vectorise dflags)
1053         $ CoreDoPasses [ simpl_gently, CoreDoVectorisation (dphPackage dflags) ]
1054
1055
1056                 -- By default, we have 2 phases before phase 0.
1057
1058                 -- Want to run with inline phase 2 after the specialiser to give
1059                 -- maximum chance for fusion to work before we inline build/augment
1060                 -- in phase 1.  This made a difference in 'ansi' where an
1061                 -- overloaded function wasn't inlined till too late.
1062
1063                 -- Need phase 1 so that build/augment get
1064                 -- inlined.  I found that spectral/hartel/genfft lost some useful
1065                 -- strictness in the function sumcode' if augment is not inlined
1066                 -- before strictness analysis runs
1067     simpl_phases = CoreDoPasses [ simpl_phase phase ["main"] max_iter
1068                                   | phase <- [phases, phases-1 .. 1] ]
1069
1070
1071         -- initial simplify: mk specialiser happy: minimum effort please
1072     simpl_gently = CoreDoSimplify SimplGently [
1073                         --      Simplify "gently"
1074                         -- Don't inline anything till full laziness has bitten
1075                         -- In particular, inlining wrappers inhibits floating
1076                         -- e.g. ...(case f x of ...)...
1077                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
1078                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
1079                         -- and now the redex (f x) isn't floatable any more
1080                         -- Similarly, don't apply any rules until after full
1081                         -- laziness.  Notably, list fusion can prevent floating.
1082
1083             NoCaseOfCase,       -- Don't do case-of-case transformations.
1084                                 -- This makes full laziness work better
1085             MaxSimplifierIterations max_iter
1086         ]
1087
1088     core_todo =
1089      if opt_level == 0 then
1090        [vectorisation,
1091         simpl_phase 0 ["final"] max_iter]
1092      else {- opt_level >= 1 -} [
1093
1094     -- We want to do the static argument transform before full laziness as it
1095     -- may expose extra opportunities to float things outwards. However, to fix
1096     -- up the output of the transformation we need at do at least one simplify
1097     -- after this before anything else
1098         runWhen static_args (CoreDoPasses [ simpl_gently, CoreDoStaticArgs ]),
1099
1100         -- We run vectorisation here for now, but we might also try to run
1101         -- it later
1102         vectorisation,
1103
1104         -- initial simplify: mk specialiser happy: minimum effort please
1105         simpl_gently,
1106
1107         -- Specialisation is best done before full laziness
1108         -- so that overloaded functions have all their dictionary lambdas manifest
1109         CoreDoSpecialising,
1110
1111         runWhen full_laziness (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
1112                 -- Was: gentleFloatOutSwitches  
1113                 -- I have no idea why, but not floating constants to top level is
1114                 -- very bad in some cases. 
1115                 -- Notably: p_ident in spectral/rewrite
1116                 --          Changing from "gentle" to "constantsOnly" improved
1117                 --          rewrite's allocation by 19%, and made  0.0% difference
1118                 --          to any other nofib benchmark
1119
1120         CoreDoFloatInwards,
1121
1122         simpl_phases,
1123
1124                 -- Phase 0: allow all Ids to be inlined now
1125                 -- This gets foldr inlined before strictness analysis
1126
1127                 -- At least 3 iterations because otherwise we land up with
1128                 -- huge dead expressions because of an infelicity in the
1129                 -- simpifier.
1130                 --      let k = BIG in foldr k z xs
1131                 -- ==>  let k = BIG in letrec go = \xs -> ...(k x).... in go xs
1132                 -- ==>  let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs
1133                 -- Don't stop now!
1134         simpl_phase 0 ["main"] (max max_iter 3),
1135
1136
1137 #ifdef OLD_STRICTNESS
1138         CoreDoOldStrictness,
1139 #endif
1140         runWhen strictness (CoreDoPasses [
1141                 CoreDoStrictness,
1142                 CoreDoWorkerWrapper,
1143                 CoreDoGlomBinds,
1144                 simpl_phase 0 ["post-worker-wrapper"] max_iter
1145                 ]),
1146
1147         runWhen full_laziness
1148           (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
1149                 -- nofib/spectral/hartel/wang doubles in speed if you
1150                 -- do full laziness late in the day.  It only happens
1151                 -- after fusion and other stuff, so the early pass doesn't
1152                 -- catch it.  For the record, the redex is
1153                 --        f_el22 (f_el21 r_midblock)
1154
1155
1156         runWhen cse CoreCSE,
1157                 -- We want CSE to follow the final full-laziness pass, because it may
1158                 -- succeed in commoning up things floated out by full laziness.
1159                 -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
1160
1161         CoreDoFloatInwards,
1162
1163         maybe_rule_check 0,
1164
1165                 -- Case-liberation for -O2.  This should be after
1166                 -- strictness analysis and the simplification which follows it.
1167         runWhen liberate_case (CoreDoPasses [
1168             CoreLiberateCase,
1169             simpl_phase 0 ["post-liberate-case"] max_iter
1170             ]),         -- Run the simplifier after LiberateCase to vastly
1171                         -- reduce the possiblility of shadowing
1172                         -- Reason: see Note [Shadowing] in SpecConstr.lhs
1173
1174         runWhen spec_constr CoreDoSpecConstr,
1175
1176         maybe_rule_check 0,
1177
1178         -- Final clean-up simplification:
1179         simpl_phase 0 ["final"] max_iter
1180      ]
1181
1182 -- -----------------------------------------------------------------------------
1183 -- StgToDo:  abstraction of stg-to-stg passes to run.
1184
1185 data StgToDo
1186   = StgDoMassageForProfiling  -- should be (next to) last
1187   -- There's also setStgVarInfo, but its absolute "lastness"
1188   -- is so critical that it is hardwired in (no flag).
1189   | D_stg_stats
1190
1191 getStgToDo :: DynFlags -> [StgToDo]
1192 getStgToDo dflags
1193   | Just todo <- stgToDo dflags = todo -- set explicitly by user
1194   | otherwise = todo2
1195   where
1196         stg_stats = dopt Opt_StgStats dflags
1197
1198         todo1 = if stg_stats then [D_stg_stats] else []
1199
1200         todo2 | WayProf `elem` wayNames dflags
1201               = StgDoMassageForProfiling : todo1
1202               | otherwise
1203               = todo1
1204
1205 -- -----------------------------------------------------------------------------
1206 -- DynFlags parser
1207
1208 allFlags :: [String]
1209 allFlags = map ('-':) $
1210            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
1211            map ("fno-"++) flags ++
1212            map ("f"++) flags ++
1213            map ("X"++) supportedLanguages ++
1214            map ("XNo"++) supportedLanguages
1215     where ok (PrefixPred _ _) = False
1216           ok _ = True
1217           flags = [ name | (name, _, _) <- fFlags ]
1218
1219 dynamic_flags :: [Flag DynP]
1220 dynamic_flags = [
1221     Flag "n"              (NoArg  (setDynFlag Opt_DryRun)) Supported
1222   , Flag "cpp"            (NoArg  (setDynFlag Opt_Cpp)) Supported
1223   , Flag "F"              (NoArg  (setDynFlag Opt_Pp)) Supported
1224   , Flag "#include"       (HasArg (addCmdlineHCInclude)) Supported
1225   , Flag "v"              (OptIntSuffix setVerbosity) Supported
1226
1227         ------- Specific phases  --------------------------------------------
1228   , Flag "pgmL"           (HasArg (upd . setPgmL)) Supported
1229   , Flag "pgmP"           (HasArg (upd . setPgmP)) Supported
1230   , Flag "pgmF"           (HasArg (upd . setPgmF)) Supported
1231   , Flag "pgmc"           (HasArg (upd . setPgmc)) Supported
1232   , Flag "pgmm"           (HasArg (upd . setPgmm)) Supported
1233   , Flag "pgms"           (HasArg (upd . setPgms)) Supported
1234   , Flag "pgma"           (HasArg (upd . setPgma)) Supported
1235   , Flag "pgml"           (HasArg (upd . setPgml)) Supported
1236   , Flag "pgmdll"         (HasArg (upd . setPgmdll)) Supported
1237   , Flag "pgmwindres"     (HasArg (upd . setPgmwindres)) Supported
1238
1239   , Flag "optL"           (HasArg (upd . addOptL)) Supported
1240   , Flag "optP"           (HasArg (upd . addOptP)) Supported
1241   , Flag "optF"           (HasArg (upd . addOptF)) Supported
1242   , Flag "optc"           (HasArg (upd . addOptc)) Supported
1243   , Flag "optm"           (HasArg (upd . addOptm)) Supported
1244   , Flag "opta"           (HasArg (upd . addOpta)) Supported
1245   , Flag "optl"           (HasArg (upd . addOptl)) Supported
1246   , Flag "optwindres"     (HasArg (upd . addOptwindres)) Supported
1247
1248   , Flag "split-objs"
1249          (NoArg (if can_split then setDynFlag Opt_SplitObjs else return ()))
1250          Supported
1251
1252         -------- ghc -M -----------------------------------------------------
1253   , Flag "dep-suffix"               (HasArg (upd . addDepSuffix)) Supported
1254   , Flag "optdep-s"                 (HasArg (upd . addDepSuffix))
1255          (Deprecated "Use -dep-suffix instead")
1256   , Flag "dep-makefile"             (HasArg (upd . setDepMakefile)) Supported
1257   , Flag "optdep-f"                 (HasArg (upd . setDepMakefile))
1258          (Deprecated "Use -dep-makefile instead")
1259   , Flag "optdep-w"                 (NoArg  (return ()))
1260          (Deprecated "-optdep-w doesn't do anything")
1261   , Flag "include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True))) Supported
1262   , Flag "optdep--include-prelude"  (NoArg  (upd (setDepIncludePkgDeps True)))
1263          (Deprecated "Use -include-pkg-deps instead")
1264   , Flag "optdep--include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True)))
1265          (Deprecated "Use -include-pkg-deps instead")
1266   , Flag "exclude-module"           (HasArg (upd . addDepExcludeMod)) Supported
1267   , Flag "optdep--exclude-module"   (HasArg (upd . addDepExcludeMod))
1268          (Deprecated "Use -exclude-module instead")
1269   , Flag "optdep-x"                 (HasArg (upd . addDepExcludeMod))
1270          (Deprecated "Use -exclude-module instead")
1271
1272         -------- Linking ----------------------------------------------------
1273   , Flag "c"              (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1274          Supported
1275   , Flag "no-link"        (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1276          (Deprecated "Use -c instead")
1277   , Flag "shared"         (NoArg (upd $ \d -> d{ ghcLink=LinkDynLib } ))
1278          Supported
1279   , Flag "dynload"        (HasArg (upd . parseDynLibLoaderMode))
1280          Supported
1281
1282         ------- Libraries ---------------------------------------------------
1283   , Flag "L"              (Prefix addLibraryPath ) Supported
1284   , Flag "l"              (AnySuffix (\s -> do upd (addOptl s))) Supported
1285
1286         ------- Frameworks --------------------------------------------------
1287         -- -framework-path should really be -F ...
1288   , Flag "framework-path" (HasArg addFrameworkPath ) Supported
1289   , Flag "framework"      (HasArg (upd . addCmdlineFramework)) Supported
1290
1291         ------- Output Redirection ------------------------------------------
1292   , Flag "odir"           (HasArg (upd . setObjectDir)) Supported
1293   , Flag "o"              (SepArg (upd . setOutputFile . Just)) Supported
1294   , Flag "ohi"            (HasArg (upd . setOutputHi   . Just )) Supported
1295   , Flag "osuf"           (HasArg (upd . setObjectSuf)) Supported
1296   , Flag "hcsuf"          (HasArg (upd . setHcSuf)) Supported
1297   , Flag "hisuf"          (HasArg (upd . setHiSuf)) Supported
1298   , Flag "hidir"          (HasArg (upd . setHiDir)) Supported
1299   , Flag "tmpdir"         (HasArg (upd . setTmpDir)) Supported
1300   , Flag "stubdir"        (HasArg (upd . setStubDir)) Supported
1301   , Flag "outputdir"      (HasArg (upd . setOutputDir)) Supported
1302   , Flag "ddump-file-prefix" (HasArg (upd . setDumpPrefixForce . Just))
1303          Supported
1304
1305         ------- Keeping temporary files -------------------------------------
1306      -- These can be singular (think ghc -c) or plural (think ghc --make)
1307   , Flag "keep-hc-file"     (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1308   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1309   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1310   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1311   , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1312   , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1313      -- This only makes sense as plural
1314   , Flag "keep-tmp-files"   (NoArg (setDynFlag Opt_KeepTmpFiles)) Supported
1315
1316         ------- Miscellaneous ----------------------------------------------
1317   , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages)) Supported
1318   , Flag "no-hs-main"     (NoArg (setDynFlag Opt_NoHsMain)) Supported
1319   , Flag "main-is"        (SepArg setMainIs ) Supported
1320   , Flag "haddock"        (NoArg (setDynFlag Opt_Haddock)) Supported
1321   , Flag "haddock-opts"   (HasArg (upd . addHaddockOpts)) Supported
1322   , Flag "hpcdir"         (SepArg setOptHpcDir) Supported
1323
1324         ------- recompilation checker --------------------------------------
1325   , Flag "recomp"         (NoArg (unSetDynFlag Opt_ForceRecomp))
1326          (Deprecated "Use -fno-force-recomp instead")
1327   , Flag "no-recomp"      (NoArg (setDynFlag   Opt_ForceRecomp))
1328          (Deprecated "Use -fforce-recomp instead")
1329
1330         ------ HsCpp opts ---------------------------------------------------
1331   , Flag "D"              (AnySuffix (upd . addOptP)) Supported
1332   , Flag "U"              (AnySuffix (upd . addOptP)) Supported
1333
1334         ------- Include/Import Paths ----------------------------------------
1335   , Flag "I"              (Prefix    addIncludePath) Supported
1336   , Flag "i"              (OptPrefix addImportPath ) Supported
1337
1338         ------ Debugging ----------------------------------------------------
1339   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats)) Supported
1340
1341   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
1342          Supported
1343   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
1344          Supported
1345   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
1346          Supported
1347   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
1348          Supported
1349   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
1350          Supported
1351   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
1352          Supported
1353   , Flag "ddump-asm-native"        (setDumpFlag Opt_D_dump_asm_native)
1354          Supported
1355   , Flag "ddump-asm-liveness"      (setDumpFlag Opt_D_dump_asm_liveness)
1356          Supported
1357   , Flag "ddump-asm-coalesce"      (setDumpFlag Opt_D_dump_asm_coalesce)
1358          Supported
1359   , Flag "ddump-asm-regalloc"      (setDumpFlag Opt_D_dump_asm_regalloc)
1360          Supported
1361   , Flag "ddump-asm-conflicts"     (setDumpFlag Opt_D_dump_asm_conflicts)
1362          Supported
1363   , Flag "ddump-asm-regalloc-stages"
1364                                  (setDumpFlag Opt_D_dump_asm_regalloc_stages)
1365          Supported
1366   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
1367          Supported
1368   , Flag "ddump-asm-expanded"      (setDumpFlag Opt_D_dump_asm_expanded)
1369          Supported
1370   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
1371          Supported
1372   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
1373          Supported
1374   , Flag "ddump-ds"                (setDumpFlag Opt_D_dump_ds)
1375          Supported
1376   , Flag "ddump-flatC"             (setDumpFlag Opt_D_dump_flatC)
1377          Supported
1378   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
1379          Supported
1380   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
1381          Supported
1382   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
1383          Supported
1384   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
1385          Supported
1386   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
1387          Supported
1388   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
1389          Supported
1390   , Flag "ddump-simpl"             (setDumpFlag Opt_D_dump_simpl)
1391          Supported
1392   , Flag "ddump-simpl-iterations"  (setDumpFlag Opt_D_dump_simpl_iterations)
1393          Supported
1394   , Flag "ddump-simpl-phases"      (OptPrefix setDumpSimplPhases)
1395          Supported
1396   , Flag "ddump-spec"              (setDumpFlag Opt_D_dump_spec)
1397          Supported
1398   , Flag "ddump-prep"              (setDumpFlag Opt_D_dump_prep)
1399          Supported
1400   , Flag "ddump-stg"               (setDumpFlag Opt_D_dump_stg)
1401          Supported
1402   , Flag "ddump-stranal"           (setDumpFlag Opt_D_dump_stranal)
1403          Supported
1404   , Flag "ddump-tc"                (setDumpFlag Opt_D_dump_tc)
1405          Supported
1406   , Flag "ddump-types"             (setDumpFlag Opt_D_dump_types)
1407          Supported
1408   , Flag "ddump-rules"             (setDumpFlag Opt_D_dump_rules)
1409          Supported
1410   , Flag "ddump-cse"               (setDumpFlag Opt_D_dump_cse)
1411          Supported
1412   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
1413          Supported
1414   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
1415          Supported
1416   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
1417          Supported
1418   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
1419          Supported
1420   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
1421          Supported
1422   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
1423          Supported
1424   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
1425          Supported
1426   , Flag "ddump-simpl-stats"       (setDumpFlag Opt_D_dump_simpl_stats)
1427          Supported
1428   , Flag "ddump-bcos"              (setDumpFlag Opt_D_dump_BCOs)
1429          Supported
1430   , Flag "dsource-stats"           (setDumpFlag Opt_D_source_stats)
1431          Supported
1432   , Flag "dverbose-core2core"      (NoArg setVerboseCore2Core)
1433          Supported
1434   , Flag "dverbose-stg2stg"        (setDumpFlag Opt_D_verbose_stg2stg)
1435          Supported
1436   , Flag "ddump-hi"                (setDumpFlag Opt_D_dump_hi)
1437          Supported
1438   , Flag "ddump-minimal-imports"   (setDumpFlag Opt_D_dump_minimal_imports)
1439          Supported
1440   , Flag "ddump-vect"              (setDumpFlag Opt_D_dump_vect)
1441          Supported
1442   , Flag "ddump-hpc"               (setDumpFlag Opt_D_dump_hpc)
1443          Supported
1444   , Flag "ddump-mod-cycles"        (setDumpFlag Opt_D_dump_mod_cycles)
1445          Supported
1446   , Flag "ddump-view-pattern-commoning" (setDumpFlag Opt_D_dump_view_pattern_commoning)
1447          Supported
1448   , Flag "ddump-to-file"           (setDumpFlag Opt_DumpToFile)
1449          Supported
1450   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
1451          Supported
1452   , Flag "ddump-rtti"              (setDumpFlag Opt_D_dump_rtti)
1453          Supported
1454
1455   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
1456          Supported
1457   , Flag "dstg-lint"               (NoArg (setDynFlag Opt_DoStgLinting))
1458          Supported
1459   , Flag "dcmm-lint"               (NoArg (setDynFlag Opt_DoCmmLinting))
1460          Supported
1461   , Flag "dasm-lint"               (NoArg (setDynFlag Opt_DoAsmLinting))
1462          Supported
1463   , Flag "dshow-passes"
1464          (NoArg (do forceRecompile
1465                     setVerbosity (Just 2)))
1466          Supported
1467   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
1468          Supported
1469
1470         ------ Machine dependant (-m<blah>) stuff ---------------------------
1471
1472   , Flag "monly-2-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 2}) ))
1473          Supported
1474   , Flag "monly-3-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 3}) ))
1475          Supported
1476   , Flag "monly-4-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 4}) ))
1477          Supported
1478
1479      ------ Warning opts -------------------------------------------------
1480   , Flag "W"      (NoArg (mapM_ setDynFlag   minusWOpts))
1481          Supported
1482   , Flag "Werror" (NoArg (setDynFlag         Opt_WarnIsError))
1483          Supported
1484   , Flag "Wwarn"  (NoArg (unSetDynFlag       Opt_WarnIsError))
1485          Supported
1486   , Flag "Wall"   (NoArg (mapM_ setDynFlag   minusWallOpts))
1487          Supported
1488   , Flag "Wnot"   (NoArg (mapM_ unSetDynFlag minusWallOpts))
1489          (Deprecated "Use -w instead")
1490   , Flag "w"      (NoArg (mapM_ unSetDynFlag minuswRemovesOpts))
1491          Supported
1492
1493         ------ Optimisation flags ------------------------------------------
1494   , Flag "O"      (NoArg (upd (setOptLevel 1))) Supported
1495   , Flag "Onot"   (NoArg (upd (setOptLevel 0)))
1496          (Deprecated "Use -O0 instead")
1497   , Flag "Odph"   (NoArg (upd setDPHOpt)) Supported
1498   , Flag "O"      (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1499          Supported
1500                 -- If the number is missing, use 1
1501
1502   , Flag "fsimplifier-phases"
1503          (IntSuffix (\n -> upd (\dfs -> dfs{ simplPhases = n })))
1504          Supported
1505   , Flag "fmax-simplifier-iterations"
1506          (IntSuffix (\n -> upd (\dfs -> dfs{ maxSimplIterations = n })))
1507          Supported
1508
1509   , Flag "fspec-constr-threshold"
1510          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrThreshold = Just n })))
1511          Supported
1512   , Flag "fno-spec-constr-threshold"
1513          (NoArg (upd (\dfs -> dfs{ specConstrThreshold = Nothing })))
1514          Supported
1515   , Flag "fspec-constr-count"
1516          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrCount = Just n })))
1517          Supported
1518   , Flag "fno-spec-constr-count"
1519          (NoArg (upd (\dfs -> dfs{ specConstrCount = Nothing })))
1520          Supported
1521   , Flag "fliberate-case-threshold"
1522          (IntSuffix (\n -> upd (\dfs -> dfs{ liberateCaseThreshold = Just n })))
1523          Supported
1524   , Flag "fno-liberate-case-threshold"
1525          (NoArg (upd (\dfs -> dfs{ liberateCaseThreshold = Nothing })))
1526          Supported
1527
1528   , Flag "frule-check"
1529          (SepArg (\s -> upd (\dfs -> dfs{ ruleCheck = Just s })))
1530          Supported
1531   , Flag "fcontext-stack"
1532          (IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
1533          Supported
1534
1535         ------ Profiling ----------------------------------------------------
1536
1537   -- XXX Should the -f* flags be deprecated?
1538   -- They don't seem to be documented
1539   , Flag "fauto-sccs-on-all-toplevs"
1540          (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1541          Supported
1542   , Flag "auto-all"
1543          (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1544          Supported
1545   , Flag "no-auto-all"
1546          (NoArg (unSetDynFlag Opt_AutoSccsOnAllToplevs))
1547          Supported
1548   , Flag "fauto-sccs-on-exported-toplevs"
1549          (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1550          Supported
1551   , Flag "auto"
1552          (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1553          Supported
1554   , Flag "no-auto"
1555          (NoArg (unSetDynFlag Opt_AutoSccsOnExportedToplevs))
1556          Supported
1557   , Flag "fauto-sccs-on-individual-cafs"
1558          (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1559          Supported
1560   , Flag "caf-all"
1561          (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1562          Supported
1563   , Flag "no-caf-all"
1564          (NoArg (unSetDynFlag Opt_AutoSccsOnIndividualCafs))
1565          Supported
1566
1567         ------ DPH flags ----------------------------------------------------
1568
1569   , Flag "fdph-seq"
1570          (NoArg (setDPHBackend DPHSeq))
1571          Supported
1572   , Flag "fdph-par"
1573          (NoArg (setDPHBackend DPHPar))
1574          Supported
1575   , Flag "fdph-this"
1576          (NoArg (setDPHBackend DPHThis))
1577          Supported
1578
1579         ------ Compiler flags -----------------------------------------------
1580
1581   , Flag "fasm"             (NoArg (setObjTarget HscAsm)) Supported
1582   , Flag "fvia-c"           (NoArg (setObjTarget HscC)) Supported
1583   , Flag "fvia-C"           (NoArg (setObjTarget HscC)) Supported
1584
1585   , Flag "fno-code"         (NoArg (setTarget HscNothing)) Supported
1586   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted)) Supported
1587   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget)) Supported
1588
1589   , Flag "fglasgow-exts"    (NoArg (mapM_ setDynFlag   glasgowExtsFlags))
1590          Supported
1591   , Flag "fno-glasgow-exts" (NoArg (mapM_ unSetDynFlag glasgowExtsFlags))
1592          Supported
1593  ]
1594  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
1595  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
1596  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
1597  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
1598
1599 package_flags :: [Flag DynP]
1600 package_flags = [
1601         ------- Packages ----------------------------------------------------
1602     Flag "package-conf"   (HasArg extraPkgConf_) Supported
1603   , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
1604          Supported
1605   , Flag "package-name"   (HasArg (upd . setPackageName)) Supported
1606   , Flag "package"        (HasArg exposePackage) Supported
1607   , Flag "hide-package"   (HasArg hidePackage) Supported
1608   , Flag "hide-all-packages" (NoArg (setDynFlag Opt_HideAllPackages))
1609          Supported
1610   , Flag "ignore-package" (HasArg ignorePackage)
1611          Supported
1612   , Flag "syslib"         (HasArg exposePackage)
1613          (Deprecated "Use -package instead")
1614   ]
1615
1616 mkFlag :: Bool                  -- ^ True <=> it should be turned on
1617        -> String                -- ^ The flag prefix
1618        -> (DynFlag -> DynP ())
1619        -> (String, DynFlag, Bool -> Deprecated)
1620        -> Flag DynP
1621 mkFlag turnOn flagPrefix f (name, dynflag, deprecated)
1622     = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
1623
1624 deprecatedForLanguage :: String -> Bool -> Deprecated
1625 deprecatedForLanguage lang turn_on
1626     = Deprecated ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ "#-} instead")
1627     where 
1628       flag | turn_on    = lang
1629            | otherwise = "No"++lang
1630
1631 useInstead :: String -> Bool -> Deprecated
1632 useInstead flag turn_on
1633   = Deprecated ("Use -f" ++ no ++ flag ++ " instead")
1634   where
1635     no = if turn_on then "" else "no-"
1636
1637 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1638 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
1639 fFlags = [
1640   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
1641   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, const Supported ),
1642   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, const Supported ),
1643   ( "warn-hi-shadowing",                Opt_WarnHiShadows, const Supported ),
1644   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, const Supported ),
1645   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, const Supported ),
1646   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, const Supported ),
1647   ( "warn-missing-fields",              Opt_WarnMissingFields, const Supported ),
1648   ( "warn-missing-methods",             Opt_WarnMissingMethods, const Supported ),
1649   ( "warn-missing-signatures",          Opt_WarnMissingSigs, const Supported ),
1650   ( "warn-name-shadowing",              Opt_WarnNameShadowing, const Supported ),
1651   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns, const Supported ),
1652   ( "warn-simple-patterns",             Opt_WarnSimplePatterns, const Supported ),
1653   ( "warn-type-defaults",               Opt_WarnTypeDefaults, const Supported ),
1654   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism, const Supported ),
1655   ( "warn-unused-binds",                Opt_WarnUnusedBinds, const Supported ),
1656   ( "warn-unused-imports",              Opt_WarnUnusedImports, const Supported ),
1657   ( "warn-unused-matches",              Opt_WarnUnusedMatches, const Supported ),
1658   ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, const Supported ),
1659   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, const Supported ),
1660   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, const Supported ),
1661   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
1662   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
1663   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, const Supported ),
1664   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
1665   ( "strictness",                       Opt_Strictness, const Supported ),
1666   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
1667   ( "full-laziness",                    Opt_FullLaziness, const Supported ),
1668   ( "liberate-case",                    Opt_LiberateCase, const Supported ),
1669   ( "spec-constr",                      Opt_SpecConstr, const Supported ),
1670   ( "cse",                              Opt_CSE, const Supported ),
1671   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas, const Supported ),
1672   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas, const Supported ),
1673   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion, const Supported ),
1674   ( "ignore-asserts",                   Opt_IgnoreAsserts, const Supported ),
1675   ( "do-eta-reduction",                 Opt_DoEtaReduction, const Supported ),
1676   ( "case-merge",                       Opt_CaseMerge, const Supported ),
1677   ( "unbox-strict-fields",              Opt_UnboxStrictFields, const Supported ),
1678   ( "method-sharing",                   Opt_MethodSharing, const Supported ),
1679   ( "dicts-cheap",                      Opt_DictsCheap, const Supported ),
1680   ( "inline-if-enough-args",            Opt_InlineIfEnoughArgs, const Supported ),
1681   ( "excess-precision",                 Opt_ExcessPrecision, const Supported ),
1682   ( "eager-blackholing",                Opt_EagerBlackHoling, const Supported ),
1683   ( "asm-mangling",                     Opt_DoAsmMangling, const Supported ),
1684   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
1685   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
1686   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
1687   ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
1688   ( "enable-rewrite-rules",             Opt_EnableRewriteRules, const Supported ),
1689   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
1690   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
1691   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
1692   ( "print-bind-contents",              Opt_PrintBindContents, const Supported ),
1693   ( "run-cps",                          Opt_RunCPS, const Supported ),
1694   ( "run-cpsz",                         Opt_RunCPSZ, const Supported ),
1695   ( "new-codegen",                      Opt_TryNewCodeGen, const Supported ),
1696   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, const Supported ),
1697   ( "vectorise",                        Opt_Vectorise, const Supported ),
1698   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
1699   ( "regs-iterative",                   Opt_RegsIterative, const Supported ),
1700   ( "th",                               Opt_TemplateHaskell,
1701     deprecatedForLanguage "TemplateHaskell" ),
1702   ( "fi",                               Opt_ForeignFunctionInterface,
1703     deprecatedForLanguage "ForeignFunctionInterface" ),
1704   ( "ffi",                              Opt_ForeignFunctionInterface,
1705     deprecatedForLanguage "ForeignFunctionInterface" ),
1706   ( "arrows",                           Opt_Arrows,
1707     deprecatedForLanguage "Arrows" ),
1708   ( "generics",                         Opt_Generics,
1709     deprecatedForLanguage "Generics" ),
1710   ( "implicit-prelude",                 Opt_ImplicitPrelude,
1711     deprecatedForLanguage "ImplicitPrelude" ),
1712   ( "bang-patterns",                    Opt_BangPatterns,
1713     deprecatedForLanguage "BangPatterns" ),
1714   ( "monomorphism-restriction",         Opt_MonomorphismRestriction,
1715     deprecatedForLanguage "MonomorphismRestriction" ),
1716   ( "mono-pat-binds",                   Opt_MonoPatBinds,
1717     deprecatedForLanguage "MonoPatBinds" ),
1718   ( "extended-default-rules",           Opt_ExtendedDefaultRules,
1719     deprecatedForLanguage "ExtendedDefaultRules" ),
1720   ( "implicit-params",                  Opt_ImplicitParams,
1721     deprecatedForLanguage "ImplicitParams" ),
1722   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
1723     deprecatedForLanguage "ScopedTypeVariables" ),
1724   ( "parr",                             Opt_PArr,
1725     deprecatedForLanguage "PArr" ),
1726   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
1727     deprecatedForLanguage "OverlappingInstances" ),
1728   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
1729     deprecatedForLanguage "UndecidableInstances" ),
1730   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
1731     deprecatedForLanguage "IncoherentInstances" ),
1732   ( "gen-manifest",                     Opt_GenManifest, const Supported ),
1733   ( "embed-manifest",                   Opt_EmbedManifest, const Supported ),
1734   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
1735   ]
1736
1737 supportedLanguages :: [String]
1738 supportedLanguages = [ name | (name, _, _) <- xFlags ]
1739
1740 -- This may contain duplicates
1741 languageOptions :: [DynFlag]
1742 languageOptions = [ dynFlag | (_, dynFlag, _) <- xFlags ]
1743
1744 -- | These -X<blah> flags can all be reversed with -XNo<blah>
1745 xFlags :: [(String, DynFlag, Bool -> Deprecated)]
1746 xFlags = [
1747   ( "CPP",                              Opt_Cpp, const Supported ),
1748   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
1749   ( "PatternGuards",                    Opt_PatternGuards, const Supported ),
1750   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, const Supported ),
1751   ( "MagicHash",                        Opt_MagicHash, const Supported ),
1752   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
1753   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
1754   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
1755   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
1756   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
1757   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
1758   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, const Supported ),
1759   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, const Supported ),
1760   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, const Supported ),
1761   ( "Rank2Types",                       Opt_Rank2Types, const Supported ),
1762   ( "RankNTypes",                       Opt_RankNTypes, const Supported ),
1763   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, const Supported ),
1764   ( "TypeOperators",                    Opt_TypeOperators, const Supported ),
1765   ( "RecursiveDo",                      Opt_RecursiveDo, const Supported ),
1766   ( "Arrows",                           Opt_Arrows, const Supported ),
1767   ( "PArr",                             Opt_PArr, const Supported ),
1768   ( "TemplateHaskell",                  Opt_TemplateHaskell, const Supported ),
1769   ( "QuasiQuotes",                      Opt_QuasiQuotes, const Supported ),
1770   ( "Generics",                         Opt_Generics, const Supported ),
1771   -- On by default:
1772   ( "ImplicitPrelude",                  Opt_ImplicitPrelude, const Supported ),
1773   ( "RecordWildCards",                  Opt_RecordWildCards, const Supported ),
1774   ( "NamedFieldPuns",                   Opt_RecordPuns, const Supported ),
1775   ( "RecordPuns",                       Opt_RecordPuns,
1776     deprecatedForLanguage "NamedFieldPuns" ),
1777   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, const Supported ),
1778   ( "OverloadedStrings",                Opt_OverloadedStrings, const Supported ),
1779   ( "GADTs",                            Opt_GADTs, const Supported ),
1780   ( "ViewPatterns",                     Opt_ViewPatterns, const Supported ),
1781   ( "TypeFamilies",                     Opt_TypeFamilies, const Supported ),
1782   ( "BangPatterns",                     Opt_BangPatterns, const Supported ),
1783   -- On by default:
1784   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, const Supported ),
1785   -- On by default (which is not strictly H98):
1786   ( "MonoPatBinds",                     Opt_MonoPatBinds, const Supported ),
1787   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
1788   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
1789   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
1790   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
1791
1792   ( "PatternSignatures",                Opt_ScopedTypeVariables, 
1793     deprecatedForLanguage "ScopedTypeVariables" ),
1794
1795   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
1796   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
1797   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
1798   ( "DeriveFunctor",                    Opt_DeriveFunctor, const Supported ),
1799   ( "DeriveTraversable",                Opt_DeriveTraversable, const Supported ),
1800   ( "DeriveFoldable",                   Opt_DeriveFoldable, const Supported ),
1801   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, const Supported ),
1802   ( "FlexibleContexts",                 Opt_FlexibleContexts, const Supported ),
1803   ( "FlexibleInstances",                Opt_FlexibleInstances, const Supported ),
1804   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods, const Supported ),
1805   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses, const Supported ),
1806   ( "FunctionalDependencies",           Opt_FunctionalDependencies, const Supported ),
1807   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, const Supported ),
1808   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
1809   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
1810   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
1811   ( "PackageImports",                   Opt_PackageImports, const Supported ),
1812   ( "NewQualifiedOperators",            Opt_NewQualifiedOperators, const Supported )
1813   ]
1814
1815 impliedFlags :: [(DynFlag, DynFlag)]
1816 impliedFlags
1817   = [ (Opt_GADTs,               Opt_RelaxedPolyRec)  -- We want type-sig variables to
1818                                                      --      be completely rigid for GADTs
1819
1820     , (Opt_TypeFamilies,        Opt_RelaxedPolyRec)  -- Trac #2944 gives a nice example
1821     , (Opt_TypeFamilies,        Opt_KindSignatures)  -- Type families use kind signatures
1822                                                      -- all over the place
1823
1824     , (Opt_ScopedTypeVariables, Opt_RelaxedPolyRec)  -- Ditto for scoped type variables; see
1825                                                      --      Note [Scoped tyvars] in TcBinds
1826     , (Opt_ImpredicativeTypes,  Opt_RankNTypes)
1827   ]
1828
1829 glasgowExtsFlags :: [DynFlag]
1830 glasgowExtsFlags = [
1831              Opt_PrintExplicitForalls
1832            , Opt_ForeignFunctionInterface
1833            , Opt_UnliftedFFITypes
1834            , Opt_GADTs
1835            , Opt_ImplicitParams
1836            , Opt_ScopedTypeVariables
1837            , Opt_UnboxedTuples
1838            , Opt_TypeSynonymInstances
1839            , Opt_StandaloneDeriving
1840            , Opt_DeriveDataTypeable
1841            , Opt_DeriveFunctor
1842            , Opt_DeriveFoldable
1843            , Opt_DeriveTraversable
1844            , Opt_FlexibleContexts
1845            , Opt_FlexibleInstances
1846            , Opt_ConstrainedClassMethods
1847            , Opt_MultiParamTypeClasses
1848            , Opt_FunctionalDependencies
1849            , Opt_MagicHash
1850            , Opt_PolymorphicComponents
1851            , Opt_ExistentialQuantification
1852            , Opt_UnicodeSyntax
1853            , Opt_PostfixOperators
1854            , Opt_PatternGuards
1855            , Opt_LiberalTypeSynonyms
1856            , Opt_RankNTypes
1857            , Opt_TypeOperators
1858            , Opt_RecursiveDo
1859            , Opt_ParallelListComp
1860            , Opt_EmptyDataDecls
1861            , Opt_KindSignatures
1862            , Opt_GeneralizedNewtypeDeriving
1863            , Opt_TypeFamilies ]
1864
1865 -- -----------------------------------------------------------------------------
1866 -- Parsing the dynamic flags.
1867
1868 -- | Parse dynamic flags from a list of command line arguments.  Returns the
1869 -- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
1870 -- Throws a 'UsageError' if errors occurred during parsing (such as unknown
1871 -- flags or missing arguments).
1872 parseDynamicFlags :: Monad m =>
1873                      DynFlags -> [Located String]
1874                   -> m (DynFlags, [Located String], [Located String])
1875                      -- ^ Updated 'DynFlags', left-over arguments, and
1876                      -- list of warnings.
1877 parseDynamicFlags dflags args = parseDynamicFlags_ dflags args True
1878
1879 -- | Like 'parseDynamicFlags' but does not allow the package flags (-package,
1880 -- -hide-package, -ignore-package, -hide-all-packages, -package-conf).
1881 parseDynamicNoPackageFlags :: Monad m =>
1882                      DynFlags -> [Located String]
1883                   -> m (DynFlags, [Located String], [Located String])
1884                      -- ^ Updated 'DynFlags', left-over arguments, and
1885                      -- list of warnings.
1886 parseDynamicNoPackageFlags dflags args = parseDynamicFlags_ dflags args False
1887
1888 parseDynamicFlags_ :: Monad m =>
1889                       DynFlags -> [Located String] -> Bool
1890                   -> m (DynFlags, [Located String], [Located String])
1891 parseDynamicFlags_ dflags args pkg_flags = do
1892   -- XXX Legacy support code
1893   -- We used to accept things like
1894   --     optdep-f  -optdepdepend
1895   --     optdep-f  -optdep depend
1896   --     optdep -f -optdepdepend
1897   --     optdep -f -optdep depend
1898   -- but the spaces trip up proper argument handling. So get rid of them.
1899   let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs
1900       f (x : xs) = x : f xs
1901       f xs = xs
1902       args' = f args
1903
1904       -- Note: -ignore-package (package_flags) must precede -i* (dynamic_flags)
1905       flag_spec | pkg_flags = package_flags ++ dynamic_flags
1906                 | otherwise = dynamic_flags
1907
1908   let ((leftover, errs, warns), dflags')
1909           = runCmdLine (processArgs flag_spec args') dflags
1910   when (not (null errs)) $ ghcError $ errorsToGhcException errs
1911   return (dflags', leftover, warns)
1912
1913 type DynP = CmdLineP DynFlags
1914
1915 upd :: (DynFlags -> DynFlags) -> DynP ()
1916 upd f = do
1917    dfs <- getCmdLineState
1918    putCmdLineState $! (f dfs)
1919
1920 --------------------------
1921 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1922 setDynFlag f = do { upd (\dfs -> dopt_set dfs f)
1923                   ; mapM_ setDynFlag deps }
1924   where
1925     deps = [ d | (f', d) <- impliedFlags, f' == f ]
1926         -- When you set f, set the ones it implies
1927         -- NB: use setDynFlag recursively, in case the implied flags
1928         --     implies further flags
1929         -- When you un-set f, however, we don't un-set the things it implies
1930         --      (except for -fno-glasgow-exts, which is treated specially)
1931
1932 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1933
1934 --------------------------
1935 setDumpFlag :: DynFlag -> OptKind DynP
1936 setDumpFlag dump_flag
1937   = NoArg (setDynFlag dump_flag >> when want_recomp forceRecompile)
1938   where
1939         -- Certain dumpy-things are really interested in what's going
1940         -- on during recompilation checking, so in those cases we
1941         -- don't want to turn it off.
1942     want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
1943                                        Opt_D_dump_hi_diffs]
1944
1945 forceRecompile :: DynP ()
1946 -- Whenver we -ddump, force recompilation (by switching off the 
1947 -- recompilation checker), else you don't see the dump! However, 
1948 -- don't switch it off in --make mode, else *everything* gets
1949 -- recompiled which probably isn't what you want
1950 forceRecompile = do { dfs <- getCmdLineState
1951                     ; when (force_recomp dfs) (setDynFlag Opt_ForceRecomp) }
1952         where
1953           force_recomp dfs = isOneShot (ghcMode dfs)
1954
1955 setVerboseCore2Core :: DynP ()
1956 setVerboseCore2Core = do setDynFlag Opt_D_verbose_core2core 
1957                          forceRecompile
1958                          upd (\s -> s { shouldDumpSimplPhase = const True })
1959
1960 setDumpSimplPhases :: String -> DynP ()
1961 setDumpSimplPhases s = do forceRecompile
1962                           upd (\s -> s { shouldDumpSimplPhase = spec })
1963   where
1964     spec :: SimplifierMode -> Bool
1965     spec = join (||)
1966          . map (join (&&) . map match . split ':')
1967          . split ','
1968          $ case s of
1969              '=' : s' -> s'
1970              _        -> s
1971
1972     join :: (Bool -> Bool -> Bool)
1973          -> [SimplifierMode -> Bool]
1974          -> SimplifierMode -> Bool
1975     join _  [] = const True
1976     join op ss = foldr1 (\f g x -> f x `op` g x) ss
1977
1978     match :: String -> SimplifierMode -> Bool
1979     match "" = const True
1980     match s  = case reads s of
1981                 [(n,"")] -> phase_num  n
1982                 _        -> phase_name s
1983
1984     phase_num :: Int -> SimplifierMode -> Bool
1985     phase_num n (SimplPhase k _) = n == k
1986     phase_num _ _                = False
1987
1988     phase_name :: String -> SimplifierMode -> Bool
1989     phase_name s SimplGently       = s == "gentle"
1990     phase_name s (SimplPhase _ ss) = s `elem` ss
1991
1992 setVerbosity :: Maybe Int -> DynP ()
1993 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1994
1995 addCmdlineHCInclude :: String -> DynP ()
1996 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1997
1998 extraPkgConf_ :: FilePath -> DynP ()
1999 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
2000
2001 exposePackage, hidePackage, ignorePackage :: String -> DynP ()
2002 exposePackage p =
2003   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
2004 hidePackage p =
2005   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
2006 ignorePackage p =
2007   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
2008
2009 setPackageName :: String -> DynFlags -> DynFlags
2010 setPackageName p
2011   | Nothing <- unpackPackageId pid
2012   = ghcError (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
2013   | otherwise
2014   = \s -> s{ thisPackage = pid }
2015   where
2016         pid = stringToPackageId p
2017
2018 -- If we're linking a binary, then only targets that produce object
2019 -- code are allowed (requests for other target types are ignored).
2020 setTarget :: HscTarget -> DynP ()
2021 setTarget l = upd set
2022   where
2023    set dfs
2024      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
2025      | otherwise = dfs
2026
2027 -- Changes the target only if we're compiling object code.  This is
2028 -- used by -fasm and -fvia-C, which switch from one to the other, but
2029 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
2030 -- can be safely used in an OPTIONS_GHC pragma.
2031 setObjTarget :: HscTarget -> DynP ()
2032 setObjTarget l = upd set
2033   where
2034    set dfs
2035      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
2036      | otherwise = dfs
2037
2038 setOptLevel :: Int -> DynFlags -> DynFlags
2039 setOptLevel n dflags
2040    | hscTarget dflags == HscInterpreted && n > 0
2041         = dflags
2042             -- not in IO any more, oh well:
2043             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
2044    | otherwise
2045         = updOptLevel n dflags
2046
2047
2048 -- -Odph is equivalent to
2049 --
2050 --    -O2                               optimise as much as possible
2051 --    -fno-method-sharing               sharing specialisation defeats fusion
2052 --                                      sometimes
2053 --    -fdicts-cheap                     always inline dictionaries
2054 --    -fmax-simplifier-iterations20     this is necessary sometimes
2055 --    -fsimplifier-phases=3             we use an additional simplifier phase
2056 --                                      for fusion
2057 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
2058 --    -fno-spec-constr-count            SpecConstr as much as possible
2059 --    -finline-enough-args              hack to prevent excessive inlining
2060 --
2061 setDPHOpt :: DynFlags -> DynFlags
2062 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
2063                                          , simplPhases         = 3
2064                                          , specConstrThreshold = Nothing
2065                                          , specConstrCount     = Nothing
2066                                          })
2067                    `dopt_set`   Opt_DictsCheap
2068                    `dopt_unset` Opt_MethodSharing
2069                    `dopt_set`   Opt_InlineIfEnoughArgs
2070
2071 data DPHBackend = DPHPar
2072                 | DPHSeq
2073                 | DPHThis
2074         deriving(Eq, Ord, Enum, Show)
2075
2076 setDPHBackend :: DPHBackend -> DynP ()
2077 setDPHBackend backend 
2078   = do
2079       upd $ \dflags -> dflags { dphBackend = backend }
2080       mapM_ exposePackage (dph_packages backend)
2081   where
2082     dph_packages DPHThis = []
2083     dph_packages DPHPar  = ["dph-prim-par", "dph-par"]
2084     dph_packages DPHSeq  = ["dph-prim-seq", "dph-seq"]
2085
2086 dphPackage :: DynFlags -> PackageId
2087 dphPackage dflags = case dphBackend dflags of
2088                       DPHPar  -> dphParPackageId
2089                       DPHSeq  -> dphSeqPackageId
2090                       DPHThis -> thisPackage dflags
2091
2092 setMainIs :: String -> DynP ()
2093 setMainIs arg
2094   | not (null main_fn) && isLower (head main_fn)
2095      -- The arg looked like "Foo.Bar.baz"
2096   = upd $ \d -> d{ mainFunIs = Just main_fn,
2097                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
2098
2099   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
2100   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
2101
2102   | otherwise                   -- The arg looked like "baz"
2103   = upd $ \d -> d{ mainFunIs = Just arg }
2104   where
2105     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
2106
2107 -- | Get the unqualified name of the function to use as the \"main\" for the main module.
2108 -- Either returns the default name or the one configured on the command line with -main-is
2109 getMainFun :: DynFlags -> RdrName
2110 getMainFun dflags = case (mainFunIs dflags) of
2111     Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn))
2112     Nothing -> main_RDR_Unqual
2113
2114 -----------------------------------------------------------------------------
2115 -- Paths & Libraries
2116
2117 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
2118
2119 -- -i on its own deletes the import paths
2120 addImportPath "" = upd (\s -> s{importPaths = []})
2121 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
2122
2123
2124 addLibraryPath p =
2125   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
2126
2127 addIncludePath p =
2128   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
2129
2130 addFrameworkPath p =
2131   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
2132
2133 #ifndef mingw32_TARGET_OS
2134 split_marker :: Char
2135 split_marker = ':'   -- not configurable (ToDo)
2136 #endif
2137
2138 splitPathList :: String -> [String]
2139 splitPathList s = filter notNull (splitUp s)
2140                 -- empty paths are ignored: there might be a trailing
2141                 -- ':' in the initial list, for example.  Empty paths can
2142                 -- cause confusion when they are translated into -I options
2143                 -- for passing to gcc.
2144   where
2145 #ifndef mingw32_TARGET_OS
2146     splitUp xs = split split_marker xs
2147 #else
2148      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
2149      --
2150      -- That is, if "foo:bar:baz" is used, this interpreted as
2151      -- consisting of three entries, 'foo', 'bar', 'baz'.
2152      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
2153      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
2154      --
2155      -- Notice that no attempt is made to fully replace the 'standard'
2156      -- split marker ':' with the Windows / DOS one, ';'. The reason being
2157      -- that this will cause too much breakage for users & ':' will
2158      -- work fine even with DOS paths, if you're not insisting on being silly.
2159      -- So, use either.
2160     splitUp []             = []
2161     splitUp (x:':':div:xs) | div `elem` dir_markers
2162                            = ((x:':':div:p): splitUp rs)
2163                            where
2164                               (p,rs) = findNextPath xs
2165           -- we used to check for existence of the path here, but that
2166           -- required the IO monad to be threaded through the command-line
2167           -- parser which is quite inconvenient.  The
2168     splitUp xs = cons p (splitUp rs)
2169                where
2170                  (p,rs) = findNextPath xs
2171
2172                  cons "" xs = xs
2173                  cons x  xs = x:xs
2174
2175     -- will be called either when we've consumed nought or the
2176     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
2177     -- finding the next split marker.
2178     findNextPath xs =
2179         case break (`elem` split_markers) xs of
2180            (p, _:ds) -> (p, ds)
2181            (p, xs)   -> (p, xs)
2182
2183     split_markers :: [Char]
2184     split_markers = [':', ';']
2185
2186     dir_markers :: [Char]
2187     dir_markers = ['/', '\\']
2188 #endif
2189
2190 -- -----------------------------------------------------------------------------
2191 -- tmpDir, where we store temporary files.
2192
2193 setTmpDir :: FilePath -> DynFlags -> DynFlags
2194 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
2195   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
2196   -- seem necessary now --SDM 7/2/2008
2197
2198 -----------------------------------------------------------------------------
2199 -- Hpc stuff
2200
2201 setOptHpcDir :: String -> DynP ()
2202 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
2203
2204 -----------------------------------------------------------------------------
2205 -- Via-C compilation stuff
2206
2207 -- There are some options that we need to pass to gcc when compiling
2208 -- Haskell code via C, but are only supported by recent versions of
2209 -- gcc.  The configure script decides which of these options we need,
2210 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
2211 -- read before each via-C compilation.  The advantage of having these
2212 -- in a separate file is that the file can be created at install-time
2213 -- depending on the available gcc version, and even re-generated  later
2214 -- if gcc is upgraded.
2215 --
2216 -- The options below are not dependent on the version of gcc, only the
2217 -- platform.
2218
2219 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
2220                               [String]) -- for registerised HC compilations
2221 machdepCCOpts _dflags
2222 #if alpha_TARGET_ARCH
2223         =       ( ["-w", "-mieee"
2224 #ifdef HAVE_THREADED_RTS_SUPPORT
2225                     , "-D_REENTRANT"
2226 #endif
2227                    ], [] )
2228         -- For now, to suppress the gcc warning "call-clobbered
2229         -- register used for global register variable", we simply
2230         -- disable all warnings altogether using the -w flag. Oh well.
2231
2232 #elif hppa_TARGET_ARCH
2233         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
2234         -- (very nice, but too bad the HP /usr/include files don't agree.)
2235         = ( ["-D_HPUX_SOURCE"], [] )
2236
2237 #elif m68k_TARGET_ARCH
2238       -- -fno-defer-pop : for the .hc files, we want all the pushing/
2239       --    popping of args to routines to be explicit; if we let things
2240       --    be deferred 'til after an STGJUMP, imminent death is certain!
2241       --
2242       -- -fomit-frame-pointer : *don't*
2243       --     It's better to have a6 completely tied up being a frame pointer
2244       --     rather than let GCC pick random things to do with it.
2245       --     (If we want to steal a6, then we would try to do things
2246       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
2247         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
2248
2249 #elif i386_TARGET_ARCH
2250       -- -fno-defer-pop : basically the same game as for m68k
2251       --
2252       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
2253       --   the fp (%ebp) for our register maps.
2254         =  let n_regs = stolen_x86_regs _dflags
2255                sta = opt_Static
2256            in
2257                     ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
2258                       ],
2259                       [ "-fno-defer-pop",
2260                         "-fomit-frame-pointer",
2261                         -- we want -fno-builtin, because when gcc inlines
2262                         -- built-in functions like memcpy() it tends to
2263                         -- run out of registers, requiring -monly-n-regs
2264                         "-fno-builtin",
2265                         "-DSTOLEN_X86_REGS="++show n_regs ]
2266                     )
2267
2268 #elif ia64_TARGET_ARCH
2269         = ( [], ["-fomit-frame-pointer", "-G0"] )
2270
2271 #elif x86_64_TARGET_ARCH
2272         = (
2273 #if darwin_TARGET_OS
2274             ["-m64"],
2275 #else
2276             [],
2277 #endif
2278                 ["-fomit-frame-pointer",
2279                  "-fno-asynchronous-unwind-tables",
2280                         -- the unwind tables are unnecessary for HC code,
2281                         -- and get in the way of -split-objs.  Another option
2282                         -- would be to throw them away in the mangler, but this
2283                         -- is easier.
2284                  "-fno-builtin"
2285                         -- calling builtins like strlen() using the FFI can
2286                         -- cause gcc to run out of regs, so use the external
2287                         -- version.
2288                 ] )
2289
2290 #elif sparc_TARGET_ARCH
2291         = ( [], ["-w"] )
2292         -- For now, to suppress the gcc warning "call-clobbered
2293         -- register used for global register variable", we simply
2294         -- disable all warnings altogether using the -w flag. Oh well.
2295
2296 #elif powerpc_apple_darwin_TARGET
2297       -- -no-cpp-precomp:
2298       --     Disable Apple's precompiling preprocessor. It's a great thing
2299       --     for "normal" programs, but it doesn't support register variable
2300       --     declarations.
2301         = ( [], ["-no-cpp-precomp"] )
2302 #else
2303         = ( [], [] )
2304 #endif
2305
2306 picCCOpts :: DynFlags -> [String]
2307 picCCOpts _dflags
2308 #if darwin_TARGET_OS
2309       -- Apple prefers to do things the other way round.
2310       -- PIC is on by default.
2311       -- -mdynamic-no-pic:
2312       --     Turn off PIC code generation.
2313       -- -fno-common:
2314       --     Don't generate "common" symbols - these are unwanted
2315       --     in dynamic libraries.
2316
2317     | opt_PIC
2318         = ["-fno-common", "-U __PIC__","-D__PIC__"]
2319     | otherwise
2320         = ["-mdynamic-no-pic"]
2321 #elif mingw32_TARGET_OS
2322       -- no -fPIC for Windows
2323     | opt_PIC
2324         = ["-U __PIC__","-D__PIC__"]
2325     | otherwise
2326         = []
2327 #else
2328     | opt_PIC || not opt_Static
2329         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
2330     | otherwise
2331         = []
2332 #endif
2333
2334 -- -----------------------------------------------------------------------------
2335 -- Splitting
2336
2337 can_split :: Bool
2338 can_split = cSplitObjs == "YES"
2339
2340 -- -----------------------------------------------------------------------------
2341 -- Compiler Info
2342
2343 compilerInfo :: [(String, String)]
2344 compilerInfo = [("Project name",                cProjectName),
2345                 ("Project version",             cProjectVersion),
2346                 ("Booter version",              cBooterVersion),
2347                 ("Stage",                       cStage),
2348                 ("Interface file version",      cHscIfaceFileVersion),
2349                 ("Have interpreter",            cGhcWithInterpreter),
2350                 ("Object splitting",            cSplitObjs),
2351                 ("Have native code generator",  cGhcWithNativeCodeGen),
2352                 ("Support SMP",                 cGhcWithSMP),
2353                 ("Unregisterised",              cGhcUnregisterised),
2354                 ("Tables next to code",         cGhcEnableTablesNextToCode),
2355                 ("Win32 DLLs",                  cEnableWin32DLLs),
2356                 ("RTS ways",                    cGhcRTSWays),
2357                 ("Leading underscore",          cLeadingUnderscore),
2358                 ("Debug on",                    show debugIsOn)
2359                ]
2360