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