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