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