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