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