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