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