9147a92dddc11fa0d42aa8e06907043f0728d207
[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        Opt_NondecreasingIndentation
811            -- strictly speaking non-standard, but we always had this
812            -- on implicitly before the option was added in 7.1, and
813            -- turning it off breaks code, so we're keeping it on for
814            -- backwards compatibility.  Cabal uses -XHaskell98 by
815            -- default unless you specify another language.
816       ]
817
818 languageExtensions (Just Haskell2010)
819     = [Opt_ImplicitPrelude,
820        Opt_MonomorphismRestriction,
821        Opt_DatatypeContexts,
822        Opt_EmptyDataDecls,
823        Opt_ForeignFunctionInterface,
824        Opt_PatternGuards,
825        Opt_DoAndIfThenElse,
826        Opt_RelaxedPolyRec]
827
828 -- | Test whether a 'DynFlag' is set
829 dopt :: DynFlag -> DynFlags -> Bool
830 dopt f dflags  = f `elem` (flags dflags)
831
832 -- | Set a 'DynFlag'
833 dopt_set :: DynFlags -> DynFlag -> DynFlags
834 dopt_set dfs f = dfs{ flags = f : flags dfs }
835
836 -- | Unset a 'DynFlag'
837 dopt_unset :: DynFlags -> DynFlag -> DynFlags
838 dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
839
840 -- | Test whether a 'ExtensionFlag' is set
841 xopt :: ExtensionFlag -> DynFlags -> Bool
842 xopt f dflags = f `elem` extensionFlags dflags
843
844 -- | Set a 'ExtensionFlag'
845 xopt_set :: DynFlags -> ExtensionFlag -> DynFlags
846 xopt_set dfs f
847     = let onoffs = On f : extensions dfs
848       in dfs { extensions = onoffs,
849                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
850
851 -- | Unset a 'ExtensionFlag'
852 xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags
853 xopt_unset dfs f
854     = let onoffs = Off f : extensions dfs
855       in dfs { extensions = onoffs,
856                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
857
858 setLanguage :: Language -> DynP ()
859 setLanguage l = upd f
860     where f dfs = let mLang = Just l
861                       oneoffs = extensions dfs
862                   in dfs {
863                          language = mLang,
864                          extensionFlags = flattenExtensionFlags mLang oneoffs
865                      }
866
867 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
868 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
869         -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
870         -> [a]                  -- ^ Correctly ordered extracted options
871 getOpts dflags opts = reverse (opts dflags)
872         -- We add to the options from the front, so we need to reverse the list
873
874 -- | Gets the verbosity flag for the current verbosity level. This is fed to
875 -- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
876 getVerbFlag :: DynFlags -> String
877 getVerbFlag dflags
878   | verbosity dflags >= 3  = "-v"
879   | otherwise =  ""
880
881 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
882          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
883          setPgmP, addOptl, addOptP,
884          addCmdlineFramework, addHaddockOpts
885    :: String -> DynFlags -> DynFlags
886 setOutputFile, setOutputHi, setDumpPrefixForce
887    :: Maybe String -> DynFlags -> DynFlags
888
889 setObjectDir  f d = d{ objectDir  = Just f}
890 setHiDir      f d = d{ hiDir      = Just f}
891 setStubDir    f d = d{ stubDir    = Just f, includePaths = f : includePaths d }
892   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
893   -- \#included from the .hc file when compiling with -fvia-C.
894 setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
895 setDylibInstallName  f d = d{ dylibInstallName = Just f}
896
897 setObjectSuf  f d = d{ objectSuf  = f}
898 setHiSuf      f d = d{ hiSuf      = f}
899 setHcSuf      f d = d{ hcSuf      = f}
900
901 setOutputFile f d = d{ outputFile = f}
902 setOutputHi   f d = d{ outputHi   = f}
903
904 parseDynLibLoaderMode f d =
905  case splitAt 8 f of
906    ("deploy", "")       -> d{ dynLibLoader = Deployable }
907    ("sysdep", "")       -> d{ dynLibLoader = SystemDependent }
908    _                    -> ghcError (CmdLineError ("Unknown dynlib loader: " ++ f))
909
910 setDumpPrefixForce f d = d { dumpPrefixForce = f}
911
912 -- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
913 -- Config.hs should really use Option.
914 setPgmP   f d = let (pgm:args) = words f in d{ pgm_P   = (pgm, map Option args)}
915 addOptl   f d = d{ opt_l   = f : opt_l d}
916 addOptP   f d = d{ opt_P   = f : opt_P d}
917
918
919 setDepMakefile :: FilePath -> DynFlags -> DynFlags
920 setDepMakefile f d = d { depMakefile = deOptDep f }
921
922 setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
923 setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
924
925 addDepExcludeMod :: String -> DynFlags -> DynFlags
926 addDepExcludeMod m d
927     = d { depExcludeMods = mkModuleName (deOptDep m) : depExcludeMods d }
928
929 addDepSuffix :: FilePath -> DynFlags -> DynFlags
930 addDepSuffix s d = d { depSuffixes = deOptDep s : depSuffixes d }
931
932 -- XXX Legacy code:
933 -- We used to use "-optdep-flag -optdeparg", so for legacy applications
934 -- we need to strip the "-optdep" off of the arg
935 deOptDep :: String -> String
936 deOptDep x = case stripPrefix "-optdep" x of
937              Just rest -> rest
938              Nothing -> x
939
940 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
941
942 addHaddockOpts f d = d{ haddockOptions = Just f}
943
944 -- -----------------------------------------------------------------------------
945 -- Command-line options
946
947 -- | When invoking external tools as part of the compilation pipeline, we
948 -- pass these a sequence of options on the command-line. Rather than
949 -- just using a list of Strings, we use a type that allows us to distinguish
950 -- between filepaths and 'other stuff'. The reason for this is that
951 -- this type gives us a handle on transforming filenames, and filenames only,
952 -- to whatever format they're expected to be on a particular platform.
953 data Option
954  = FileOption -- an entry that _contains_ filename(s) / filepaths.
955               String  -- a non-filepath prefix that shouldn't be
956                       -- transformed (e.g., "/out=")
957               String  -- the filepath/filename portion
958  | Option     String
959
960 showOpt :: Option -> String
961 showOpt (FileOption pre f) = pre ++ f
962 showOpt (Option s)  = s
963
964 -----------------------------------------------------------------------------
965 -- Setting the optimisation level
966
967 updOptLevel :: Int -> DynFlags -> DynFlags
968 -- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
969 updOptLevel n dfs
970   = dfs2{ optLevel = final_n }
971   where
972    final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
973    dfs1 = foldr (flip dopt_unset) dfs  remove_dopts
974    dfs2 = foldr (flip dopt_set)   dfs1 extra_dopts
975
976    extra_dopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
977    remove_dopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
978
979 -- -----------------------------------------------------------------------------
980 -- StgToDo:  abstraction of stg-to-stg passes to run.
981
982 data StgToDo
983   = StgDoMassageForProfiling  -- should be (next to) last
984   -- There's also setStgVarInfo, but its absolute "lastness"
985   -- is so critical that it is hardwired in (no flag).
986   | D_stg_stats
987
988 getStgToDo :: DynFlags -> [StgToDo]
989 getStgToDo dflags
990   = todo2
991   where
992         stg_stats = dopt Opt_StgStats dflags
993
994         todo1 = if stg_stats then [D_stg_stats] else []
995
996         todo2 | WayProf `elem` wayNames dflags
997               = StgDoMassageForProfiling : todo1
998               | otherwise
999               = todo1
1000
1001 {- **********************************************************************
1002 %*                                                                      *
1003                 DynFlags parser
1004 %*                                                                      *
1005 %********************************************************************* -}
1006
1007 -- -----------------------------------------------------------------------------
1008 -- Parsing the dynamic flags.
1009
1010 -- | Parse dynamic flags from a list of command line arguments.  Returns the
1011 -- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
1012 -- Throws a 'UsageError' if errors occurred during parsing (such as unknown
1013 -- flags or missing arguments).
1014 parseDynamicFlags :: Monad m =>
1015                      DynFlags -> [Located String]
1016                   -> m (DynFlags, [Located String], [Located String])
1017                      -- ^ Updated 'DynFlags', left-over arguments, and
1018                      -- list of warnings.
1019 parseDynamicFlags dflags args = parseDynamicFlags_ dflags args True
1020
1021 -- | Like 'parseDynamicFlags' but does not allow the package flags (-package,
1022 -- -hide-package, -ignore-package, -hide-all-packages, -package-conf).
1023 parseDynamicNoPackageFlags :: Monad m =>
1024                      DynFlags -> [Located String]
1025                   -> m (DynFlags, [Located String], [Located String])
1026                      -- ^ Updated 'DynFlags', left-over arguments, and
1027                      -- list of warnings.
1028 parseDynamicNoPackageFlags dflags args = parseDynamicFlags_ dflags args False
1029
1030 parseDynamicFlags_ :: Monad m =>
1031                       DynFlags -> [Located String] -> Bool
1032                   -> m (DynFlags, [Located String], [Located String])
1033 parseDynamicFlags_ dflags0 args pkg_flags = do
1034   -- XXX Legacy support code
1035   -- We used to accept things like
1036   --     optdep-f  -optdepdepend
1037   --     optdep-f  -optdep depend
1038   --     optdep -f -optdepdepend
1039   --     optdep -f -optdep depend
1040   -- but the spaces trip up proper argument handling. So get rid of them.
1041   let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs
1042       f (x : xs) = x : f xs
1043       f xs = xs
1044       args' = f args
1045
1046       -- Note: -ignore-package (package_flags) must precede -i* (dynamic_flags)
1047       flag_spec | pkg_flags = package_flags ++ dynamic_flags
1048                 | otherwise = dynamic_flags
1049
1050   let ((leftover, errs, warns), dflags1)
1051           = runCmdLine (processArgs flag_spec args') dflags0
1052   when (not (null errs)) $ ghcError $ errorsToGhcException errs
1053
1054   -- Cannot use -fPIC with registerised -fvia-C, because the mangler
1055   -- isn't up to the job.  We know that if hscTarget == HscC, then the
1056   -- user has explicitly used -fvia-C, because -fasm is the default,
1057   -- unless there is no NCG on this platform.  The latter case is
1058   -- checked when the -fPIC flag is parsed.
1059   --
1060   let (pic_warns, dflags2)
1061         | opt_PIC && hscTarget dflags1 == HscC && cGhcUnregisterised == "NO"
1062         = ([L noSrcSpan $ "Warning: -fvia-C is incompatible with -fPIC; ignoring -fvia-C"],
1063                 dflags1{ hscTarget = HscAsm })
1064 #if !(x86_64_TARGET_ARCH && linux_TARGET_OS)
1065         | (not opt_Static || opt_PIC) && hscTarget dflags1 == HscLlvm
1066         = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and -"
1067                 ++ "dynamic on this platform;\n              ignoring -fllvm"],
1068                 dflags1{ hscTarget = HscAsm })
1069 #endif
1070         | otherwise = ([], dflags1)
1071
1072   return (dflags2, leftover, pic_warns ++ warns)
1073
1074
1075 {- **********************************************************************
1076 %*                                                                      *
1077                 DynFlags specifications
1078 %*                                                                      *
1079 %********************************************************************* -}
1080
1081 allFlags :: [String]
1082 allFlags = map ('-':) $
1083            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
1084            map ("fno-"++) flags ++
1085            map ("f"++) flags ++
1086            map ("f"++) flags' ++
1087            map ("X"++) supportedExtensions
1088     where ok (PrefixPred _ _) = False
1089           ok _ = True
1090           flags = [ name | (name, _, _) <- fFlags ]
1091           flags' = [ name | (name, _, _) <- fLangFlags ]
1092
1093 --------------- The main flags themselves ------------------
1094 dynamic_flags :: [Flag (CmdLineP DynFlags)]
1095 dynamic_flags = [
1096     Flag "n"        (NoArg (setDynFlag Opt_DryRun))
1097   , Flag "cpp"      (NoArg (setExtensionFlag Opt_Cpp)) 
1098   , Flag "F"        (NoArg (setDynFlag Opt_Pp)) 
1099   , Flag "#include" 
1100          (HasArg (\s -> do { addCmdlineHCInclude s
1101                            ; addWarn "-#include and INCLUDE pragmas are deprecated: They no longer have any effect" }))
1102   , Flag "v"        (OptIntSuffix setVerbosity)
1103
1104         ------- Specific phases  --------------------------------------------
1105     -- need to appear before -pgmL to be parsed as LLVM flags.
1106   , Flag "pgmlo"          (hasArg (\f d -> d{ pgm_lo  = (f,[])}))
1107   , Flag "pgmlc"          (hasArg (\f d -> d{ pgm_lc  = (f,[])}))
1108   , Flag "pgmL"           (hasArg (\f d -> d{ pgm_L   = f}))
1109   , Flag "pgmP"           (hasArg setPgmP)
1110   , Flag "pgmF"           (hasArg (\f d -> d{ pgm_F   = f}))
1111   , Flag "pgmc"           (hasArg (\f d -> d{ pgm_c   = (f,[])}))
1112   , Flag "pgmm"           (hasArg (\f d -> d{ pgm_m   = (f,[])}))
1113   , Flag "pgms"           (hasArg (\f d -> d{ pgm_s   = (f,[])}))
1114   , Flag "pgma"           (hasArg (\f d -> d{ pgm_a   = (f,[])}))
1115   , Flag "pgml"           (hasArg (\f d -> d{ pgm_l   = (f,[])}))
1116   , Flag "pgmdll"         (hasArg (\f d -> d{ pgm_dll = (f,[])}))
1117   , Flag "pgmwindres"     (hasArg (\f d -> d{ pgm_windres = f}))
1118
1119     -- need to appear before -optl/-opta to be parsed as LLVM flags.
1120   , Flag "optlo"          (hasArg (\f d -> d{ opt_lo  = f : opt_lo d}))
1121   , Flag "optlc"          (hasArg (\f d -> d{ opt_lc  = f : opt_lc d}))
1122   , Flag "optL"           (hasArg (\f d -> d{ opt_L   = f : opt_L d}))
1123   , Flag "optP"           (hasArg addOptP)
1124   , Flag "optF"           (hasArg (\f d -> d{ opt_F   = f : opt_F d}))
1125   , Flag "optc"           (hasArg (\f d -> d{ opt_c   = f : opt_c d}))
1126   , Flag "optm"           (hasArg (\f d -> d{ opt_m   = f : opt_m d}))
1127   , Flag "opta"           (hasArg (\f d -> d{ opt_a   = f : opt_a d}))
1128   , Flag "optl"           (hasArg addOptl)
1129   , Flag "optwindres"     (hasArg (\f d -> d{ opt_windres = f : opt_windres d}))
1130
1131   , Flag "split-objs"
1132          (NoArg (if can_split 
1133                  then setDynFlag Opt_SplitObjs
1134                  else addWarn "ignoring -fsplit-objs"))
1135
1136         -------- ghc -M -----------------------------------------------------
1137   , Flag "dep-suffix"     (hasArg addDepSuffix)
1138   , Flag "optdep-s"       (hasArgDF addDepSuffix "Use -dep-suffix instead")
1139   , Flag "dep-makefile"   (hasArg setDepMakefile)
1140   , Flag "optdep-f"       (hasArgDF setDepMakefile "Use -dep-makefile instead")
1141   , Flag "optdep-w"       (NoArg  (deprecate "doesn't do anything"))
1142   , Flag "include-pkg-deps"         (noArg (setDepIncludePkgDeps True))
1143   , Flag "optdep--include-prelude"  (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
1144   , Flag "optdep--include-pkg-deps" (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
1145   , Flag "exclude-module"           (hasArg addDepExcludeMod)
1146   , Flag "optdep--exclude-module"   (hasArgDF addDepExcludeMod "Use -exclude-module instead")
1147   , Flag "optdep-x"                 (hasArgDF addDepExcludeMod "Use -exclude-module instead")
1148
1149         -------- Linking ----------------------------------------------------
1150   , Flag "no-link"            (noArg (\d -> d{ ghcLink=NoLink }))
1151   , Flag "shared"             (noArg (\d -> d{ ghcLink=LinkDynLib }))
1152   , Flag "dynload"            (hasArg parseDynLibLoaderMode)
1153   , Flag "dylib-install-name" (hasArg setDylibInstallName)
1154
1155         ------- Libraries ---------------------------------------------------
1156   , Flag "L"   (Prefix    addLibraryPath)
1157   , Flag "l"   (AnySuffix (upd . addOptl))
1158
1159         ------- Frameworks --------------------------------------------------
1160         -- -framework-path should really be -F ...
1161   , Flag "framework-path" (HasArg addFrameworkPath)
1162   , Flag "framework"      (hasArg addCmdlineFramework)
1163
1164         ------- Output Redirection ------------------------------------------
1165   , Flag "odir"              (hasArg setObjectDir)
1166   , Flag "o"                 (SepArg (upd . setOutputFile . Just))
1167   , Flag "ohi"               (hasArg (setOutputHi . Just ))
1168   , Flag "osuf"              (hasArg setObjectSuf)
1169   , Flag "hcsuf"             (hasArg setHcSuf)
1170   , Flag "hisuf"             (hasArg setHiSuf)
1171   , Flag "hidir"             (hasArg setHiDir)
1172   , Flag "tmpdir"            (hasArg setTmpDir)
1173   , Flag "stubdir"           (hasArg setStubDir)
1174   , Flag "outputdir"         (hasArg setOutputDir)
1175   , Flag "ddump-file-prefix" (hasArg (setDumpPrefixForce . Just))
1176
1177         ------- Keeping temporary files -------------------------------------
1178      -- These can be singular (think ghc -c) or plural (think ghc --make)
1179   , Flag "keep-hc-file"     (NoArg (setDynFlag Opt_KeepHcFiles))
1180   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles))
1181   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles))
1182   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles))
1183   , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles))
1184   , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles))
1185   , Flag "keep-llvm-file"   (NoArg (setDynFlag Opt_KeepLlvmFiles))
1186   , Flag "keep-llvm-files"  (NoArg (setDynFlag Opt_KeepLlvmFiles))
1187      -- This only makes sense as plural
1188   , Flag "keep-tmp-files"   (NoArg (setDynFlag Opt_KeepTmpFiles))
1189
1190         ------- Miscellaneous ----------------------------------------------
1191   , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages))
1192   , Flag "no-hs-main"     (NoArg (setDynFlag Opt_NoHsMain))
1193   , Flag "with-rtsopts"   (HasArg setRtsOpts)
1194   , Flag "rtsopts"        (NoArg (setRtsOptsEnabled RtsOptsAll))
1195   , Flag "rtsopts=all"    (NoArg (setRtsOptsEnabled RtsOptsAll))
1196   , Flag "rtsopts=some"   (NoArg (setRtsOptsEnabled RtsOptsSafeOnly))
1197   , Flag "rtsopts=none"   (NoArg (setRtsOptsEnabled RtsOptsNone))
1198   , Flag "no-rtsopts"     (NoArg (setRtsOptsEnabled RtsOptsNone))
1199   , Flag "main-is"        (SepArg setMainIs)
1200   , Flag "haddock"        (NoArg (setDynFlag Opt_Haddock))
1201   , Flag "haddock-opts"   (hasArg addHaddockOpts)
1202   , Flag "hpcdir"         (SepArg setOptHpcDir)
1203
1204         ------- recompilation checker --------------------------------------
1205   , Flag "recomp"         (NoArg (do { unSetDynFlag Opt_ForceRecomp
1206                                      ; deprecate "Use -fno-force-recomp instead" }))
1207   , Flag "no-recomp"      (NoArg (do { setDynFlag Opt_ForceRecomp
1208                                      ; deprecate "Use -fforce-recomp instead" }))
1209
1210         ------ HsCpp opts ---------------------------------------------------
1211   , Flag "D"              (AnySuffix (upd . addOptP))
1212   , Flag "U"              (AnySuffix (upd . addOptP))
1213
1214         ------- Include/Import Paths ----------------------------------------
1215   , Flag "I"              (Prefix    addIncludePath)
1216   , Flag "i"              (OptPrefix addImportPath)
1217
1218         ------ Debugging ----------------------------------------------------
1219   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats))
1220
1221   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
1222   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
1223   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
1224   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
1225   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
1226   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
1227   , Flag "ddump-asm-native"        (setDumpFlag Opt_D_dump_asm_native)
1228   , Flag "ddump-asm-liveness"      (setDumpFlag Opt_D_dump_asm_liveness)
1229   , Flag "ddump-asm-coalesce"      (setDumpFlag Opt_D_dump_asm_coalesce)
1230   , Flag "ddump-asm-regalloc"      (setDumpFlag Opt_D_dump_asm_regalloc)
1231   , Flag "ddump-asm-conflicts"     (setDumpFlag Opt_D_dump_asm_conflicts)
1232   , Flag "ddump-asm-regalloc-stages" (setDumpFlag Opt_D_dump_asm_regalloc_stages)
1233   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
1234   , Flag "ddump-asm-expanded"      (setDumpFlag Opt_D_dump_asm_expanded)
1235   , Flag "ddump-llvm"              (NoArg (do { setObjTarget HscLlvm
1236                                               ; setDumpFlag' Opt_D_dump_llvm}))
1237   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
1238   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
1239   , Flag "ddump-ds"                (setDumpFlag Opt_D_dump_ds)
1240   , Flag "ddump-flatC"             (setDumpFlag Opt_D_dump_flatC)
1241   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
1242   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
1243   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
1244   , Flag "ddump-rule-rewrites"     (setDumpFlag Opt_D_dump_rule_rewrites)
1245   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
1246   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
1247   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
1248   , Flag "ddump-simpl"             (setDumpFlag Opt_D_dump_simpl)
1249   , Flag "ddump-simpl-iterations"  (setDumpFlag Opt_D_dump_simpl_iterations)
1250   , Flag "ddump-simpl-phases"      (OptPrefix setDumpSimplPhases)
1251   , Flag "ddump-spec"              (setDumpFlag Opt_D_dump_spec)
1252   , Flag "ddump-prep"              (setDumpFlag Opt_D_dump_prep)
1253   , Flag "ddump-stg"               (setDumpFlag Opt_D_dump_stg)
1254   , Flag "ddump-stranal"           (setDumpFlag Opt_D_dump_stranal)
1255   , Flag "ddump-tc"                (setDumpFlag Opt_D_dump_tc)
1256   , Flag "ddump-types"             (setDumpFlag Opt_D_dump_types)
1257   , Flag "ddump-rules"             (setDumpFlag Opt_D_dump_rules)
1258   , Flag "ddump-cse"               (setDumpFlag Opt_D_dump_cse)
1259   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
1260   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
1261   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
1262   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
1263   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
1264   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
1265   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
1266   , Flag "ddump-simpl-stats"       (setDumpFlag Opt_D_dump_simpl_stats)
1267   , Flag "ddump-bcos"              (setDumpFlag Opt_D_dump_BCOs)
1268   , Flag "dsource-stats"           (setDumpFlag Opt_D_source_stats)
1269   , Flag "dverbose-core2core"      (NoArg (do { setVerbosity (Just 2)
1270                                               ; setVerboseCore2Core }))
1271   , Flag "dverbose-stg2stg"        (setDumpFlag Opt_D_verbose_stg2stg)
1272   , Flag "ddump-hi"                (setDumpFlag Opt_D_dump_hi)
1273   , Flag "ddump-minimal-imports"   (setDumpFlag Opt_D_dump_minimal_imports)
1274   , Flag "ddump-vect"              (setDumpFlag Opt_D_dump_vect)
1275   , Flag "ddump-hpc"               (setDumpFlag Opt_D_dump_hpc)
1276   , Flag "ddump-mod-cycles"        (setDumpFlag Opt_D_dump_mod_cycles)
1277   , Flag "ddump-view-pattern-commoning" (setDumpFlag Opt_D_dump_view_pattern_commoning)
1278   , Flag "ddump-to-file"           (setDumpFlag Opt_DumpToFile)
1279   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
1280   , Flag "ddump-rtti"              (setDumpFlag Opt_D_dump_rtti)
1281   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
1282   , Flag "dstg-lint"               (NoArg (setDynFlag Opt_DoStgLinting))
1283   , Flag "dcmm-lint"               (NoArg (setDynFlag Opt_DoCmmLinting))
1284   , Flag "dasm-lint"               (NoArg (setDynFlag Opt_DoAsmLinting))
1285   , Flag "dshow-passes"            (NoArg (do forceRecompile
1286                                               setVerbosity (Just 2)))
1287   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
1288
1289         ------ Machine dependant (-m<blah>) stuff ---------------------------
1290
1291   , Flag "monly-2-regs" (noArg (\s -> s{stolen_x86_regs = 2}))
1292   , Flag "monly-3-regs" (noArg (\s -> s{stolen_x86_regs = 3}))
1293   , Flag "monly-4-regs" (noArg (\s -> s{stolen_x86_regs = 4}))
1294   , Flag "msse2"        (NoArg (setDynFlag Opt_SSE2))
1295
1296      ------ Warning opts -------------------------------------------------
1297   , Flag "W"      (NoArg (mapM_ setDynFlag   minusWOpts))
1298   , Flag "Werror" (NoArg (setDynFlag         Opt_WarnIsError))
1299   , Flag "Wwarn"  (NoArg (unSetDynFlag       Opt_WarnIsError))
1300   , Flag "Wall"   (NoArg (mapM_ setDynFlag   minusWallOpts))
1301   , Flag "Wnot"   (NoArg (do { mapM_ unSetDynFlag minusWallOpts
1302                              ; deprecate "Use -w instead" }))
1303   , Flag "w"      (NoArg (mapM_ unSetDynFlag minuswRemovesOpts))
1304
1305         ------ Optimisation flags ------------------------------------------
1306   , Flag "O"      (noArg (setOptLevel 1))
1307   , Flag "Onot"   (noArgDF (setOptLevel 0) "Use -O0 instead")
1308   , Flag "Odph"   (noArg setDPHOpt)
1309   , Flag "O"      (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1310                 -- If the number is missing, use 1
1311
1312   , Flag "fsimplifier-phases"          (intSuffix (\n d -> d{ simplPhases = n }))
1313   , Flag "fmax-simplifier-iterations"  (intSuffix (\n d -> d{ maxSimplIterations = n }))
1314   , Flag "fspec-constr-threshold"      (intSuffix (\n d -> d{ specConstrThreshold = Just n }))
1315   , Flag "fno-spec-constr-threshold"   (noArg (\d -> d{ specConstrThreshold = Nothing }))
1316   , Flag "fspec-constr-count"          (intSuffix (\n d -> d{ specConstrCount = Just n }))
1317   , Flag "fno-spec-constr-count"       (noArg (\d -> d{ specConstrCount = Nothing }))
1318   , Flag "fliberate-case-threshold"    (intSuffix (\n d -> d{ liberateCaseThreshold = Just n }))
1319   , Flag "fno-liberate-case-threshold" (noArg (\d -> d{ liberateCaseThreshold = Nothing }))
1320   , Flag "frule-check"                 (SepArg (\s -> upd (\d -> d{ ruleCheck = Just s })))
1321   , Flag "fcontext-stack"              (intSuffix (\n d -> d{ ctxtStkDepth = n }))
1322   , Flag "fstrictness-before"          (intSuffix (\n d -> d{ strictnessBefore = n : strictnessBefore d }))
1323   , Flag "ffloat-lam-args"             (intSuffix (\n d -> d{ floatLamArgs = Just n }))
1324   , Flag "ffloat-all-lams"             (intSuffix (\n d -> d{ floatLamArgs = Nothing }))
1325
1326         ------ Profiling ----------------------------------------------------
1327
1328   -- XXX Should the -f* flags be deprecated?
1329   -- They don't seem to be documented
1330   , Flag "fauto-sccs-on-all-toplevs"       (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1331   , Flag "auto-all"                        (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1332   , Flag "no-auto-all"                     (NoArg (unSetDynFlag Opt_AutoSccsOnAllToplevs))
1333   , Flag "fauto-sccs-on-exported-toplevs"  (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1334   , Flag "auto"                            (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1335   , Flag "no-auto"                         (NoArg (unSetDynFlag Opt_AutoSccsOnExportedToplevs))
1336   , Flag "fauto-sccs-on-individual-cafs"   (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1337   , Flag "caf-all"                         (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1338   , Flag "no-caf-all"                      (NoArg (unSetDynFlag Opt_AutoSccsOnIndividualCafs))
1339
1340         ------ DPH flags ----------------------------------------------------
1341
1342   , Flag "fdph-seq"         (NoArg (setDPHBackend DPHSeq))
1343   , Flag "fdph-par"         (NoArg (setDPHBackend DPHPar))
1344   , Flag "fdph-this"        (NoArg (setDPHBackend DPHThis))
1345   , Flag "fdph-none"        (NoArg (setDPHBackend DPHNone))
1346
1347         ------ Compiler flags -----------------------------------------------
1348
1349   , Flag "fasm"             (NoArg (setObjTarget HscAsm))
1350   , Flag "fvia-c"           (NoArg (setObjTarget HscC >>
1351          (addWarn "The -fvia-c flag will be removed in a future GHC release")))
1352   , Flag "fvia-C"           (NoArg (setObjTarget HscC >>
1353          (addWarn "The -fvia-C flag will be removed in a future GHC release")))
1354   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm))
1355
1356   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
1357                                        setTarget HscNothing))
1358   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted))
1359   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget))
1360   , Flag "fglasgow-exts"    (NoArg (enableGlasgowExts >> deprecate "Use individual extensions instead"))
1361   , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use individual extensions instead"))
1362  ]
1363  ++ map (mkFlag turnOn  "f"    setDynFlag  ) fFlags
1364  ++ map (mkFlag turnOff "fno-" unSetDynFlag) fFlags
1365  ++ map (mkFlag turnOn  "f"    setExtensionFlag  ) fLangFlags
1366  ++ map (mkFlag turnOff "fno-" unSetExtensionFlag) fLangFlags
1367  ++ map (mkFlag turnOn  "X"    setExtensionFlag  ) xFlags
1368  ++ map (mkFlag turnOff "XNo"  unSetExtensionFlag) xFlags
1369  ++ map (mkFlag turnOn  "X"    setLanguage) languageFlags
1370
1371 package_flags :: [Flag (CmdLineP DynFlags)]
1372 package_flags = [
1373         ------- Packages ----------------------------------------------------
1374     Flag "package-conf"         (HasArg extraPkgConf_)
1375   , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
1376   , Flag "package-name"         (hasArg setPackageName)
1377   , Flag "package-id"           (HasArg exposePackageId)
1378   , Flag "package"              (HasArg exposePackage)
1379   , Flag "hide-package"         (HasArg hidePackage)
1380   , Flag "hide-all-packages"    (NoArg (setDynFlag Opt_HideAllPackages))
1381   , Flag "ignore-package"       (HasArg ignorePackage)
1382   , Flag "syslib"               (HasArg (\s -> do { exposePackage s
1383                                                   ; deprecate "Use -package instead" }))
1384   ]
1385
1386 type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
1387                          -- False <=> we are turning the flag off
1388 turnOn  :: TurnOnFlag; turnOn = True
1389 turnOff :: TurnOnFlag; turnOff = False
1390
1391 type FlagSpec flag
1392    = ( String   -- Flag in string form
1393      , flag     -- Flag in internal form
1394      , TurnOnFlag -> DynP ())    -- Extra action to run when the flag is found
1395                                  -- Typically, emit a warning or error
1396
1397 mkFlag :: TurnOnFlag            -- ^ True <=> it should be turned on
1398        -> String                -- ^ The flag prefix
1399        -> (flag -> DynP ())     -- ^ What to do when the flag is found
1400        -> FlagSpec flag         -- ^ Specification of this particular flag
1401        -> Flag (CmdLineP DynFlags)
1402 mkFlag turn_on flagPrefix f (name, flag, extra_action)
1403     = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turn_on))
1404
1405 deprecatedForExtension :: String -> TurnOnFlag -> DynP ()
1406 deprecatedForExtension lang turn_on
1407     = deprecate ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead")
1408     where 
1409       flag | turn_on    = lang
1410            | otherwise = "No"++lang
1411
1412 useInstead :: String -> TurnOnFlag -> DynP ()
1413 useInstead flag turn_on
1414   = deprecate ("Use -f" ++ no ++ flag ++ " instead")
1415   where
1416     no = if turn_on then "" else "no-"
1417
1418 nop :: TurnOnFlag -> DynP ()
1419 nop _ = return ()
1420
1421 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1422 fFlags :: [FlagSpec DynFlag]
1423 fFlags = [
1424   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, nop ),
1425   ( "warn-dodgy-exports",               Opt_WarnDodgyExports, nop ),
1426   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, nop ),
1427   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, nop ),
1428   ( "warn-hi-shadowing",                Opt_WarnHiShadows, nop ),
1429   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, nop ),
1430   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, nop ),
1431   ( "warn-incomplete-uni-patterns",     Opt_WarnIncompleteUniPatterns, nop ),
1432   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, nop ),
1433   ( "warn-missing-fields",              Opt_WarnMissingFields, nop ),
1434   ( "warn-missing-import-lists",        Opt_WarnMissingImportList, nop ),
1435   ( "warn-missing-methods",             Opt_WarnMissingMethods, nop ),
1436   ( "warn-missing-signatures",          Opt_WarnMissingSigs, nop ),
1437   ( "warn-missing-local-sigs",          Opt_WarnMissingLocalSigs, nop ),
1438   ( "warn-name-shadowing",              Opt_WarnNameShadowing, nop ),
1439   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns, nop ),
1440   ( "warn-type-defaults",               Opt_WarnTypeDefaults, nop ),
1441   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism, nop ),
1442   ( "warn-unused-binds",                Opt_WarnUnusedBinds, nop ),
1443   ( "warn-unused-imports",              Opt_WarnUnusedImports, nop ),
1444   ( "warn-unused-matches",              Opt_WarnUnusedMatches, nop ),
1445   ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, nop ),
1446   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, nop ),
1447   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, nop ),
1448   ( "warn-orphans",                     Opt_WarnOrphans, nop ),
1449   ( "warn-identities",                  Opt_WarnIdentities, nop ),
1450   ( "warn-auto-orphans",                Opt_WarnAutoOrphans, nop ),
1451   ( "warn-tabs",                        Opt_WarnTabs, nop ),
1452   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, nop ),
1453   ( "warn-lazy-unlifted-bindings",      Opt_WarnLazyUnliftedBindings, nop),
1454   ( "warn-unused-do-bind",              Opt_WarnUnusedDoBind, nop ),
1455   ( "warn-wrong-do-bind",               Opt_WarnWrongDoBind, nop ),
1456   ( "warn-alternative-layout-rule-transitional", Opt_WarnAlternativeLayoutRuleTransitional, nop ),
1457   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, nop ),
1458   ( "strictness",                       Opt_Strictness, nop ),
1459   ( "specialise",                       Opt_Specialise, nop ),
1460   ( "float-in",                         Opt_FloatIn, nop ),
1461   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, nop ),
1462   ( "full-laziness",                    Opt_FullLaziness, nop ),
1463   ( "liberate-case",                    Opt_LiberateCase, nop ),
1464   ( "spec-constr",                      Opt_SpecConstr, nop ),
1465   ( "cse",                              Opt_CSE, nop ),
1466   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas, nop ),
1467   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas, nop ),
1468   ( "expose-all-unfoldings",            Opt_ExposeAllUnfoldings, nop ),
1469   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion, nop ),
1470   ( "ignore-asserts",                   Opt_IgnoreAsserts, nop ),
1471   ( "do-eta-reduction",                 Opt_DoEtaReduction, nop ),
1472   ( "case-merge",                       Opt_CaseMerge, nop ),
1473   ( "unbox-strict-fields",              Opt_UnboxStrictFields, nop ),
1474   ( "method-sharing",                   Opt_MethodSharing, 
1475      \_ -> deprecate "doesn't do anything any more"),
1476      -- Remove altogether in GHC 7.2
1477   ( "dicts-cheap",                      Opt_DictsCheap, nop ),
1478   ( "excess-precision",                 Opt_ExcessPrecision, nop ),
1479   ( "eager-blackholing",                Opt_EagerBlackHoling, nop ),
1480   ( "asm-mangling",                     Opt_DoAsmMangling, nop ),
1481   ( "print-bind-result",                Opt_PrintBindResult, nop ),
1482   ( "force-recomp",                     Opt_ForceRecomp, nop ),
1483   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, nop ),
1484   ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
1485   ( "enable-rewrite-rules",             Opt_EnableRewriteRules, nop ),
1486   ( "break-on-exception",               Opt_BreakOnException, nop ),
1487   ( "break-on-error",                   Opt_BreakOnError, nop ),
1488   ( "print-evld-with-show",             Opt_PrintEvldWithShow, nop ),
1489   ( "print-bind-contents",              Opt_PrintBindContents, nop ),
1490   ( "run-cps",                          Opt_RunCPS, nop ),
1491   ( "run-cpsz",                         Opt_RunCPSZ, nop ),
1492   ( "new-codegen",                      Opt_TryNewCodeGen, nop ),
1493   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, nop ),
1494   ( "vectorise",                        Opt_Vectorise, nop ),
1495   ( "regs-graph",                       Opt_RegsGraph, nop ),
1496   ( "regs-iterative",                   Opt_RegsIterative, nop ),
1497   ( "gen-manifest",                     Opt_GenManifest, nop ),
1498   ( "embed-manifest",                   Opt_EmbedManifest, nop ),
1499   ( "ext-core",                         Opt_EmitExternalCore, nop ),
1500   ( "shared-implib",                    Opt_SharedImplib, nop ),
1501   ( "ghci-sandbox",                     Opt_GhciSandbox, nop ),
1502   ( "helpful-errors",                   Opt_HelpfulErrors, nop ),
1503   ( "building-cabal-package",           Opt_BuildingCabalPackage, nop ),
1504   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, nop )
1505   ]
1506
1507 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1508 fLangFlags :: [FlagSpec ExtensionFlag]
1509 fLangFlags = [
1510   ( "th",                               Opt_TemplateHaskell,
1511     deprecatedForExtension "TemplateHaskell" >> checkTemplateHaskellOk ),
1512   ( "fi",                               Opt_ForeignFunctionInterface,
1513     deprecatedForExtension "ForeignFunctionInterface" ),
1514   ( "ffi",                              Opt_ForeignFunctionInterface,
1515     deprecatedForExtension "ForeignFunctionInterface" ),
1516   ( "arrows",                           Opt_Arrows,
1517     deprecatedForExtension "Arrows" ),
1518   ( "generics",                         Opt_Generics,
1519     deprecatedForExtension "Generics" ),
1520   ( "implicit-prelude",                 Opt_ImplicitPrelude,
1521     deprecatedForExtension "ImplicitPrelude" ),
1522   ( "bang-patterns",                    Opt_BangPatterns,
1523     deprecatedForExtension "BangPatterns" ),
1524   ( "monomorphism-restriction",         Opt_MonomorphismRestriction,
1525     deprecatedForExtension "MonomorphismRestriction" ),
1526   ( "mono-pat-binds",                   Opt_MonoPatBinds,
1527     deprecatedForExtension "MonoPatBinds" ),
1528   ( "extended-default-rules",           Opt_ExtendedDefaultRules,
1529     deprecatedForExtension "ExtendedDefaultRules" ),
1530   ( "implicit-params",                  Opt_ImplicitParams,
1531     deprecatedForExtension "ImplicitParams" ),
1532   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
1533     deprecatedForExtension "ScopedTypeVariables" ),
1534   ( "parr",                             Opt_ParallelArrays,
1535     deprecatedForExtension "ParallelArrays" ),
1536   ( "PArr",                             Opt_ParallelArrays,
1537     deprecatedForExtension "ParallelArrays" ),
1538   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
1539     deprecatedForExtension "OverlappingInstances" ),
1540   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
1541     deprecatedForExtension "UndecidableInstances" ),
1542   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
1543     deprecatedForExtension "IncoherentInstances" )
1544   ]
1545
1546 supportedLanguages :: [String]
1547 supportedLanguages = [ name | (name, _, _) <- languageFlags ]
1548
1549 supportedExtensions :: [String]
1550 supportedExtensions = [ name' | (name, _, _) <- xFlags, name' <- [name, "No" ++ name] ]
1551
1552 supportedLanguagesAndExtensions :: [String]
1553 supportedLanguagesAndExtensions = supportedLanguages ++ supportedExtensions
1554
1555 -- | These -X<blah> flags cannot be reversed with -XNo<blah>
1556 languageFlags :: [FlagSpec Language]
1557 languageFlags = [
1558   ( "Haskell98",                        Haskell98, nop ),
1559   ( "Haskell2010",                      Haskell2010, nop )
1560   ]
1561
1562 -- | These -X<blah> flags can all be reversed with -XNo<blah>
1563 xFlags :: [FlagSpec ExtensionFlag]
1564 xFlags = [
1565   ( "CPP",                              Opt_Cpp, nop ),
1566   ( "PostfixOperators",                 Opt_PostfixOperators, nop ),
1567   ( "TupleSections",                    Opt_TupleSections, nop ),
1568   ( "PatternGuards",                    Opt_PatternGuards, nop ),
1569   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, nop ),
1570   ( "MagicHash",                        Opt_MagicHash, nop ),
1571   ( "PolymorphicComponents",            Opt_PolymorphicComponents, nop ),
1572   ( "ExistentialQuantification",        Opt_ExistentialQuantification, nop ),
1573   ( "KindSignatures",                   Opt_KindSignatures, nop ),
1574   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, nop ),
1575   ( "ParallelListComp",                 Opt_ParallelListComp, nop ),
1576   ( "TransformListComp",                Opt_TransformListComp, nop ),
1577   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, nop ),
1578   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, nop ),
1579   ( "GHCForeignImportPrim",             Opt_GHCForeignImportPrim, nop ),
1580   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, nop ),
1581   ( "Rank2Types",                       Opt_Rank2Types, nop ),
1582   ( "RankNTypes",                       Opt_RankNTypes, nop ),
1583   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, nop), 
1584   ( "TypeOperators",                    Opt_TypeOperators, nop ),
1585   ( "RecursiveDo",                      Opt_RecursiveDo,
1586     deprecatedForExtension "DoRec"),
1587   ( "DoRec",                            Opt_DoRec, nop ),
1588   ( "Arrows",                           Opt_Arrows, nop ),
1589   ( "ParallelArrays",                   Opt_ParallelArrays, nop ),
1590   ( "TemplateHaskell",                  Opt_TemplateHaskell, checkTemplateHaskellOk ),
1591   ( "QuasiQuotes",                      Opt_QuasiQuotes, nop ),
1592   ( "Generics",                         Opt_Generics, nop ),
1593   ( "ImplicitPrelude",                  Opt_ImplicitPrelude, nop ),
1594   ( "RecordWildCards",                  Opt_RecordWildCards, nop ),
1595   ( "NamedFieldPuns",                   Opt_RecordPuns, nop ),
1596   ( "RecordPuns",                       Opt_RecordPuns,
1597     deprecatedForExtension "NamedFieldPuns" ),
1598   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, nop ),
1599   ( "OverloadedStrings",                Opt_OverloadedStrings, nop ),
1600   ( "GADTs",                            Opt_GADTs, nop ),
1601   ( "GADTSyntax",                       Opt_GADTSyntax, nop ),
1602   ( "ViewPatterns",                     Opt_ViewPatterns, nop ),
1603   ( "TypeFamilies",                     Opt_TypeFamilies, nop ),
1604   ( "BangPatterns",                     Opt_BangPatterns, nop ),
1605   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, nop ),
1606   ( "NPlusKPatterns",                   Opt_NPlusKPatterns, nop ),
1607   ( "DoAndIfThenElse",                  Opt_DoAndIfThenElse, nop ),
1608   ( "RebindableSyntax",                 Opt_RebindableSyntax, nop ),
1609   ( "MonoPatBinds",                     Opt_MonoPatBinds, nop ),
1610   ( "ExplicitForAll",                   Opt_ExplicitForAll, nop ),
1611   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, nop ),
1612   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, nop ),
1613   ( "DatatypeContexts",                 Opt_DatatypeContexts, nop ),
1614   ( "NondecreasingIndentation",         Opt_NondecreasingIndentation, nop ),
1615   ( "RelaxedLayout",                    Opt_RelaxedLayout, nop ),
1616   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, nop ),
1617   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, 
1618     \ turn_on -> if not turn_on 
1619                  then deprecate "You can't turn off RelaxedPolyRec any more"
1620                  else return () ),
1621   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, nop ),
1622   ( "ImplicitParams",                   Opt_ImplicitParams, nop ),
1623   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, nop ),
1624
1625   ( "PatternSignatures",                Opt_ScopedTypeVariables, 
1626     deprecatedForExtension "ScopedTypeVariables" ),
1627
1628   ( "UnboxedTuples",                    Opt_UnboxedTuples, nop ),
1629   ( "StandaloneDeriving",               Opt_StandaloneDeriving, nop ),
1630   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, nop ),
1631   ( "DeriveFunctor",                    Opt_DeriveFunctor, nop ),
1632   ( "DeriveTraversable",                Opt_DeriveTraversable, nop ),
1633   ( "DeriveFoldable",                   Opt_DeriveFoldable, nop ),
1634   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, nop ),
1635   ( "FlexibleContexts",                 Opt_FlexibleContexts, nop ),
1636   ( "FlexibleInstances",                Opt_FlexibleInstances, nop ),
1637   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods, nop ),
1638   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses, nop ),
1639   ( "FunctionalDependencies",           Opt_FunctionalDependencies, nop ),
1640   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, nop ),
1641   ( "OverlappingInstances",             Opt_OverlappingInstances, nop ),
1642   ( "UndecidableInstances",             Opt_UndecidableInstances, nop ),
1643   ( "IncoherentInstances",              Opt_IncoherentInstances, nop ),
1644   ( "PackageImports",                   Opt_PackageImports, nop )
1645   ]
1646
1647 defaultFlags :: [DynFlag]
1648 defaultFlags 
1649   = [ Opt_AutoLinkPackages,
1650       Opt_ReadUserPackageConf,
1651
1652       Opt_DoAsmMangling,
1653
1654       Opt_SharedImplib,
1655
1656       Opt_GenManifest,
1657       Opt_EmbedManifest,
1658       Opt_PrintBindContents,
1659       Opt_GhciSandbox,
1660       Opt_HelpfulErrors
1661     ]
1662
1663     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
1664              -- The default -O0 options
1665
1666     ++ standardWarnings
1667
1668 impliedFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)]
1669 impliedFlags
1670   = [ (Opt_RankNTypes,                turnOn, Opt_ExplicitForAll)
1671     , (Opt_Rank2Types,                turnOn, Opt_ExplicitForAll)
1672     , (Opt_ScopedTypeVariables,       turnOn, Opt_ExplicitForAll)
1673     , (Opt_LiberalTypeSynonyms,       turnOn, Opt_ExplicitForAll)
1674     , (Opt_ExistentialQuantification, turnOn, Opt_ExplicitForAll)
1675     , (Opt_PolymorphicComponents,     turnOn, Opt_ExplicitForAll)
1676     , (Opt_FlexibleInstances,         turnOn, Opt_TypeSynonymInstances)
1677
1678     , (Opt_RebindableSyntax, turnOff, Opt_ImplicitPrelude)      -- NB: turn off!
1679
1680     , (Opt_GADTs,            turnOn, Opt_GADTSyntax)
1681     , (Opt_GADTs,            turnOn, Opt_MonoLocalBinds)
1682     , (Opt_TypeFamilies,     turnOn, Opt_MonoLocalBinds)
1683
1684     , (Opt_TypeFamilies,     turnOn, Opt_KindSignatures)  -- Type families use kind signatures
1685                                                      -- all over the place
1686
1687     , (Opt_ImpredicativeTypes,  turnOn, Opt_RankNTypes)
1688
1689         -- Record wild-cards implies field disambiguation
1690         -- Otherwise if you write (C {..}) you may well get
1691         -- stuff like " 'a' not in scope ", which is a bit silly
1692         -- if the compiler has just filled in field 'a' of constructor 'C'
1693     , (Opt_RecordWildCards,     turnOn, Opt_DisambiguateRecordFields)
1694     
1695     , (Opt_ParallelArrays, turnOn, Opt_ParallelListComp)
1696   ]
1697
1698 optLevelFlags :: [([Int], DynFlag)]
1699 optLevelFlags
1700   = [ ([0],     Opt_IgnoreInterfacePragmas)
1701     , ([0],     Opt_OmitInterfacePragmas)
1702
1703     , ([1,2],   Opt_IgnoreAsserts)
1704     , ([1,2],   Opt_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
1705                                          --              in PrelRules
1706     , ([1,2],   Opt_DoEtaReduction)
1707     , ([1,2],   Opt_CaseMerge)
1708     , ([1,2],   Opt_Strictness)
1709     , ([1,2],   Opt_CSE)
1710     , ([1,2],   Opt_FullLaziness)
1711     , ([1,2],   Opt_Specialise)
1712     , ([1,2],   Opt_FloatIn)
1713
1714     , ([2],     Opt_LiberateCase)
1715     , ([2],     Opt_SpecConstr)
1716     , ([2],     Opt_RegsGraph)
1717
1718 --     , ([2],     Opt_StaticArgumentTransformation)
1719 -- Max writes: I think it's probably best not to enable SAT with -O2 for the
1720 -- 6.10 release. The version of SAT in HEAD at the moment doesn't incorporate
1721 -- several improvements to the heuristics, and I'm concerned that without
1722 -- those changes SAT will interfere with some attempts to write "high
1723 -- performance Haskell", as we saw in some posts on Haskell-Cafe earlier
1724 -- this year. In particular, the version in HEAD lacks the tail call
1725 -- criterion, so many things that look like reasonable loops will be
1726 -- turned into functions with extra (unneccesary) thunk creation.
1727
1728     , ([0,1,2], Opt_DoLambdaEtaExpansion)
1729                 -- This one is important for a tiresome reason:
1730                 -- we want to make sure that the bindings for data
1731                 -- constructors are eta-expanded.  This is probably
1732                 -- a good thing anyway, but it seems fragile.
1733     ]
1734
1735 -- -----------------------------------------------------------------------------
1736 -- Standard sets of warning options
1737
1738 standardWarnings :: [DynFlag]
1739 standardWarnings
1740     = [ Opt_WarnWarningsDeprecations,
1741         Opt_WarnDeprecatedFlags,
1742         Opt_WarnUnrecognisedPragmas,
1743         Opt_WarnOverlappingPatterns,
1744         Opt_WarnMissingFields,
1745         Opt_WarnMissingMethods,
1746         Opt_WarnDuplicateExports,
1747         Opt_WarnLazyUnliftedBindings,
1748         Opt_WarnDodgyForeignImports,
1749         Opt_WarnWrongDoBind,
1750         Opt_WarnAlternativeLayoutRuleTransitional
1751       ]
1752
1753 minusWOpts :: [DynFlag]
1754 -- Things you get with -W
1755 minusWOpts
1756     = standardWarnings ++
1757       [ Opt_WarnUnusedBinds,
1758         Opt_WarnUnusedMatches,
1759         Opt_WarnUnusedImports,
1760         Opt_WarnIncompletePatterns,
1761         Opt_WarnDodgyExports,
1762         Opt_WarnDodgyImports
1763       ]
1764
1765 minusWallOpts :: [DynFlag]
1766 -- Things you get with -Wall
1767 minusWallOpts
1768     = minusWOpts ++
1769       [ Opt_WarnTypeDefaults,
1770         Opt_WarnNameShadowing,
1771         Opt_WarnMissingSigs,
1772         Opt_WarnHiShadows,
1773         Opt_WarnOrphans,
1774         Opt_WarnUnusedDoBind
1775       ]
1776
1777 minuswRemovesOpts :: [DynFlag]
1778 -- minuswRemovesOpts should be every warning option 
1779 minuswRemovesOpts
1780     = minusWallOpts ++
1781       [Opt_WarnTabs,
1782        Opt_WarnIncompletePatternsRecUpd,
1783        Opt_WarnIncompleteUniPatterns,
1784        Opt_WarnMonomorphism,
1785        Opt_WarnUnrecognisedPragmas,
1786        Opt_WarnAutoOrphans,
1787        Opt_WarnImplicitPrelude
1788      ]       
1789
1790 enableGlasgowExts :: DynP ()
1791 enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
1792                        mapM_ setExtensionFlag glasgowExtsFlags
1793
1794 disableGlasgowExts :: DynP ()
1795 disableGlasgowExts = do unSetDynFlag Opt_PrintExplicitForalls
1796                         mapM_ unSetExtensionFlag glasgowExtsFlags
1797
1798 glasgowExtsFlags :: [ExtensionFlag]
1799 glasgowExtsFlags = [
1800              Opt_ForeignFunctionInterface
1801            , Opt_UnliftedFFITypes
1802            , Opt_ImplicitParams
1803            , Opt_ScopedTypeVariables
1804            , Opt_UnboxedTuples
1805            , Opt_TypeSynonymInstances
1806            , Opt_StandaloneDeriving
1807            , Opt_DeriveDataTypeable
1808            , Opt_DeriveFunctor
1809            , Opt_DeriveFoldable
1810            , Opt_DeriveTraversable
1811            , Opt_FlexibleContexts
1812            , Opt_FlexibleInstances
1813            , Opt_ConstrainedClassMethods
1814            , Opt_MultiParamTypeClasses
1815            , Opt_FunctionalDependencies
1816            , Opt_MagicHash
1817            , Opt_PolymorphicComponents
1818            , Opt_ExistentialQuantification
1819            , Opt_UnicodeSyntax
1820            , Opt_PostfixOperators
1821            , Opt_PatternGuards
1822            , Opt_LiberalTypeSynonyms
1823            , Opt_RankNTypes
1824            , Opt_TypeOperators
1825            , Opt_DoRec
1826            , Opt_ParallelListComp
1827            , Opt_EmptyDataDecls
1828            , Opt_KindSignatures
1829            , Opt_GeneralizedNewtypeDeriving ]
1830
1831 #ifdef GHCI
1832 -- Consult the RTS to find whether GHC itself has been built profiled
1833 -- If so, you can't use Template Haskell
1834 foreign import ccall unsafe "rts_isProfiled" rtsIsProfiledIO :: IO CInt
1835
1836 rtsIsProfiled :: Bool
1837 rtsIsProfiled = unsafePerformIO rtsIsProfiledIO /= 0
1838
1839 checkTemplateHaskellOk :: Bool -> DynP ()
1840 checkTemplateHaskellOk turn_on 
1841   | turn_on && rtsIsProfiled
1842   = addErr "You can't use Template Haskell with a profiled compiler"
1843   | otherwise
1844   = return ()
1845 #else
1846 -- In stage 1 we don't know that the RTS has rts_isProfiled, 
1847 -- so we simply say "ok".  It doesn't matter because TH isn't
1848 -- available in stage 1 anyway.
1849 checkTemplateHaskellOk turn_on = return ()
1850 #endif
1851
1852 {- **********************************************************************
1853 %*                                                                      *
1854                 DynFlags constructors
1855 %*                                                                      *
1856 %********************************************************************* -}
1857
1858 type DynP = EwM (CmdLineP DynFlags)
1859
1860 upd :: (DynFlags -> DynFlags) -> DynP ()
1861 upd f = liftEwM (do { dfs <- getCmdLineState
1862                     ; putCmdLineState $! (f dfs) })
1863
1864 --------------- Constructor functions for OptKind -----------------
1865 noArg :: (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1866 noArg fn = NoArg (upd fn)
1867
1868 noArgDF :: (DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
1869 noArgDF fn deprec = NoArg (upd fn >> deprecate deprec)
1870
1871 hasArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1872 hasArg fn = HasArg (upd . fn)
1873
1874 hasArgDF :: (String -> DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
1875 hasArgDF fn deprec = HasArg (\s -> do { upd (fn s)
1876                                       ; deprecate deprec })
1877
1878 intSuffix :: (Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1879 intSuffix fn = IntSuffix (\n -> upd (fn n))
1880
1881 setDumpFlag :: DynFlag -> OptKind (CmdLineP DynFlags)
1882 setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag)
1883
1884 --------------------------
1885 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1886 setDynFlag   f = upd (\dfs -> dopt_set dfs f)
1887 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1888
1889 --------------------------
1890 setExtensionFlag, unSetExtensionFlag :: ExtensionFlag -> DynP ()
1891 setExtensionFlag f = do { upd (\dfs -> xopt_set dfs f)
1892                         ; sequence_ deps }
1893   where
1894     deps = [ if turn_on then setExtensionFlag   d
1895                         else unSetExtensionFlag d
1896            | (f', turn_on, d) <- impliedFlags, f' == f ]
1897         -- When you set f, set the ones it implies
1898         -- NB: use setExtensionFlag recursively, in case the implied flags
1899         --     implies further flags
1900
1901 unSetExtensionFlag f = upd (\dfs -> xopt_unset dfs f)
1902    -- When you un-set f, however, we don't un-set the things it implies
1903    --      (except for -fno-glasgow-exts, which is treated specially)
1904
1905 --------------------------
1906 setDumpFlag' :: DynFlag -> DynP ()
1907 setDumpFlag' dump_flag
1908   = do { setDynFlag dump_flag
1909        ; when want_recomp forceRecompile }
1910   where
1911         -- Certain dumpy-things are really interested in what's going
1912         -- on during recompilation checking, so in those cases we
1913         -- don't want to turn it off.
1914     want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
1915                                        Opt_D_dump_hi_diffs]
1916
1917 forceRecompile :: DynP ()
1918 -- Whenver we -ddump, force recompilation (by switching off the 
1919 -- recompilation checker), else you don't see the dump! However, 
1920 -- don't switch it off in --make mode, else *everything* gets
1921 -- recompiled which probably isn't what you want
1922 forceRecompile = do { dfs <- liftEwM getCmdLineState
1923                     ; when (force_recomp dfs) (setDynFlag Opt_ForceRecomp) }
1924         where
1925           force_recomp dfs = isOneShot (ghcMode dfs)
1926
1927 setVerboseCore2Core :: DynP ()
1928 setVerboseCore2Core = do forceRecompile
1929                          setDynFlag Opt_D_verbose_core2core 
1930                          upd (\dfs -> dfs { shouldDumpSimplPhase = Nothing })
1931                          
1932
1933 setDumpSimplPhases :: String -> DynP ()
1934 setDumpSimplPhases s = do forceRecompile
1935                           upd (\dfs -> dfs { shouldDumpSimplPhase = Just spec })
1936   where
1937     spec = case s of { ('=' : s') -> s';  _ -> s }
1938
1939 setVerbosity :: Maybe Int -> DynP ()
1940 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1941
1942 addCmdlineHCInclude :: String -> DynP ()
1943 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1944
1945 extraPkgConf_ :: FilePath -> DynP ()
1946 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
1947
1948 exposePackage, exposePackageId, hidePackage, ignorePackage :: String -> DynP ()
1949 exposePackage p =
1950   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
1951 exposePackageId p =
1952   upd (\s -> s{ packageFlags = ExposePackageId p : packageFlags s })
1953 hidePackage p =
1954   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
1955 ignorePackage p =
1956   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
1957
1958 setPackageName :: String -> DynFlags -> DynFlags
1959 setPackageName p s =  s{ thisPackage = stringToPackageId p }
1960
1961 -- If we're linking a binary, then only targets that produce object
1962 -- code are allowed (requests for other target types are ignored).
1963 setTarget :: HscTarget -> DynP ()
1964 setTarget l = upd set
1965   where
1966    set dfs
1967      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
1968      | otherwise = dfs
1969
1970 -- Changes the target only if we're compiling object code.  This is
1971 -- used by -fasm and -fvia-C, which switch from one to the other, but
1972 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
1973 -- can be safely used in an OPTIONS_GHC pragma.
1974 setObjTarget :: HscTarget -> DynP ()
1975 setObjTarget l = upd set
1976   where
1977    set dfs
1978      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
1979      | otherwise = dfs
1980
1981 setOptLevel :: Int -> DynFlags -> DynFlags
1982 setOptLevel n dflags
1983    | hscTarget dflags == HscInterpreted && n > 0
1984         = dflags
1985             -- not in IO any more, oh well:
1986             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
1987    | otherwise
1988         = updOptLevel n dflags
1989
1990
1991 -- -Odph is equivalent to
1992 --
1993 --    -O2                               optimise as much as possible
1994 --    -fmax-simplifier-iterations20     this is necessary sometimes
1995 --    -fsimplifier-phases=3             we use an additional simplifier phase for fusion
1996 --
1997 setDPHOpt :: DynFlags -> DynFlags
1998 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
1999                                          , simplPhases         = 3
2000                                          })
2001
2002 -- Determines the package used by the vectoriser for the symbols of the vectorised code.
2003 -- 'DPHNone' indicates that no data-parallel backend library is available; hence, the
2004 -- vectoriser cannot be used.
2005 --
2006 data DPHBackend = DPHPar    -- "dph-par"
2007                 | DPHSeq    -- "dph-seq"
2008                 | DPHThis   -- the currently compiled package
2009                 | DPHNone   -- no DPH library available
2010         deriving(Eq, Ord, Enum, Show)
2011
2012 setDPHBackend :: DPHBackend -> DynP ()
2013 setDPHBackend backend = upd $ \dflags -> dflags { dphBackend = backend }
2014
2015 -- Query the DPH backend package to be used by the vectoriser.
2016 --
2017 dphPackage :: DynFlags -> PackageId
2018 dphPackage dflags 
2019   = case dphBackend dflags of
2020       DPHPar  -> dphParPackageId
2021       DPHSeq  -> dphSeqPackageId
2022       DPHThis -> thisPackage dflags
2023       DPHNone -> ghcError (CmdLineError dphBackendError)
2024
2025 dphBackendError :: String
2026 dphBackendError = "To use -fvectorise select a DPH backend with -fdph-par or -fdph-seq"
2027
2028 setMainIs :: String -> DynP ()
2029 setMainIs arg
2030   | not (null main_fn) && isLower (head main_fn)
2031      -- The arg looked like "Foo.Bar.baz"
2032   = upd $ \d -> d{ mainFunIs = Just main_fn,
2033                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
2034
2035   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
2036   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
2037
2038   | otherwise                   -- The arg looked like "baz"
2039   = upd $ \d -> d{ mainFunIs = Just arg }
2040   where
2041     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
2042
2043 -----------------------------------------------------------------------------
2044 -- Paths & Libraries
2045
2046 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
2047
2048 -- -i on its own deletes the import paths
2049 addImportPath "" = upd (\s -> s{importPaths = []})
2050 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
2051
2052
2053 addLibraryPath p =
2054   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
2055
2056 addIncludePath p =
2057   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
2058
2059 addFrameworkPath p =
2060   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
2061
2062 #ifndef mingw32_TARGET_OS
2063 split_marker :: Char
2064 split_marker = ':'   -- not configurable (ToDo)
2065 #endif
2066
2067 splitPathList :: String -> [String]
2068 splitPathList s = filter notNull (splitUp s)
2069                 -- empty paths are ignored: there might be a trailing
2070                 -- ':' in the initial list, for example.  Empty paths can
2071                 -- cause confusion when they are translated into -I options
2072                 -- for passing to gcc.
2073   where
2074 #ifndef mingw32_TARGET_OS
2075     splitUp xs = split split_marker xs
2076 #else
2077      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
2078      --
2079      -- That is, if "foo:bar:baz" is used, this interpreted as
2080      -- consisting of three entries, 'foo', 'bar', 'baz'.
2081      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
2082      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
2083      --
2084      -- Notice that no attempt is made to fully replace the 'standard'
2085      -- split marker ':' with the Windows / DOS one, ';'. The reason being
2086      -- that this will cause too much breakage for users & ':' will
2087      -- work fine even with DOS paths, if you're not insisting on being silly.
2088      -- So, use either.
2089     splitUp []             = []
2090     splitUp (x:':':div:xs) | div `elem` dir_markers
2091                            = ((x:':':div:p): splitUp rs)
2092                            where
2093                               (p,rs) = findNextPath xs
2094           -- we used to check for existence of the path here, but that
2095           -- required the IO monad to be threaded through the command-line
2096           -- parser which is quite inconvenient.  The
2097     splitUp xs = cons p (splitUp rs)
2098                where
2099                  (p,rs) = findNextPath xs
2100
2101                  cons "" xs = xs
2102                  cons x  xs = x:xs
2103
2104     -- will be called either when we've consumed nought or the
2105     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
2106     -- finding the next split marker.
2107     findNextPath xs =
2108         case break (`elem` split_markers) xs of
2109            (p, _:ds) -> (p, ds)
2110            (p, xs)   -> (p, xs)
2111
2112     split_markers :: [Char]
2113     split_markers = [':', ';']
2114
2115     dir_markers :: [Char]
2116     dir_markers = ['/', '\\']
2117 #endif
2118
2119 -- -----------------------------------------------------------------------------
2120 -- tmpDir, where we store temporary files.
2121
2122 setTmpDir :: FilePath -> DynFlags -> DynFlags
2123 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
2124   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
2125   -- seem necessary now --SDM 7/2/2008
2126
2127 -----------------------------------------------------------------------------
2128 -- RTS opts
2129
2130 setRtsOpts :: String -> DynP ()
2131 setRtsOpts arg  = upd $ \ d -> d {rtsOpts = Just arg}
2132
2133 setRtsOptsEnabled :: RtsOptsEnabled -> DynP ()
2134 setRtsOptsEnabled arg  = upd $ \ d -> d {rtsOptsEnabled = arg}
2135
2136 -----------------------------------------------------------------------------
2137 -- Hpc stuff
2138
2139 setOptHpcDir :: String -> DynP ()
2140 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
2141
2142 -----------------------------------------------------------------------------
2143 -- Via-C compilation stuff
2144
2145 -- There are some options that we need to pass to gcc when compiling
2146 -- Haskell code via C, but are only supported by recent versions of
2147 -- gcc.  The configure script decides which of these options we need,
2148 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
2149 -- read before each via-C compilation.  The advantage of having these
2150 -- in a separate file is that the file can be created at install-time
2151 -- depending on the available gcc version, and even re-generated  later
2152 -- if gcc is upgraded.
2153 --
2154 -- The options below are not dependent on the version of gcc, only the
2155 -- platform.
2156
2157 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
2158                               [String]) -- for registerised HC compilations
2159 machdepCCOpts dflags = let (flagsAll, flagsRegHc) = machdepCCOpts' dflags
2160                        in (cCcOpts ++ flagsAll, flagsRegHc)
2161
2162 machdepCCOpts' :: DynFlags -> ([String], -- flags for all C compilations
2163                                [String]) -- for registerised HC compilations
2164 machdepCCOpts' _dflags
2165 #if alpha_TARGET_ARCH
2166         =       ( ["-w", "-mieee"
2167 #ifdef HAVE_THREADED_RTS_SUPPORT
2168                     , "-D_REENTRANT"
2169 #endif
2170                    ], [] )
2171         -- For now, to suppress the gcc warning "call-clobbered
2172         -- register used for global register variable", we simply
2173         -- disable all warnings altogether using the -w flag. Oh well.
2174
2175 #elif hppa_TARGET_ARCH
2176         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
2177         -- (very nice, but too bad the HP /usr/include files don't agree.)
2178         = ( ["-D_HPUX_SOURCE"], [] )
2179
2180 #elif m68k_TARGET_ARCH
2181       -- -fno-defer-pop : for the .hc files, we want all the pushing/
2182       --    popping of args to routines to be explicit; if we let things
2183       --    be deferred 'til after an STGJUMP, imminent death is certain!
2184       --
2185       -- -fomit-frame-pointer : *don't*
2186       --     It's better to have a6 completely tied up being a frame pointer
2187       --     rather than let GCC pick random things to do with it.
2188       --     (If we want to steal a6, then we would try to do things
2189       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
2190         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
2191
2192 #elif i386_TARGET_ARCH
2193       -- -fno-defer-pop : basically the same game as for m68k
2194       --
2195       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
2196       --   the fp (%ebp) for our register maps.
2197         =  let n_regs = stolen_x86_regs _dflags
2198            in
2199                     (
2200                       [ if opt_Static then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
2201                       ],
2202                       [ "-fno-defer-pop",
2203                         "-fomit-frame-pointer",
2204                         -- we want -fno-builtin, because when gcc inlines
2205                         -- built-in functions like memcpy() it tends to
2206                         -- run out of registers, requiring -monly-n-regs
2207                         "-fno-builtin",
2208                         "-DSTOLEN_X86_REGS="++show n_regs ]
2209                     )
2210
2211 #elif ia64_TARGET_ARCH
2212         = ( [], ["-fomit-frame-pointer", "-G0"] )
2213
2214 #elif x86_64_TARGET_ARCH
2215         = (
2216                 [],
2217                 ["-fomit-frame-pointer",
2218                  "-fno-asynchronous-unwind-tables",
2219                         -- the unwind tables are unnecessary for HC code,
2220                         -- and get in the way of -split-objs.  Another option
2221                         -- would be to throw them away in the mangler, but this
2222                         -- is easier.
2223                  "-fno-builtin"
2224                         -- calling builtins like strlen() using the FFI can
2225                         -- cause gcc to run out of regs, so use the external
2226                         -- version.
2227                 ] )
2228
2229 #elif sparc_TARGET_ARCH
2230         = ( [], ["-w"] )
2231         -- For now, to suppress the gcc warning "call-clobbered
2232         -- register used for global register variable", we simply
2233         -- disable all warnings altogether using the -w flag. Oh well.
2234
2235 #elif powerpc_apple_darwin_TARGET
2236       -- -no-cpp-precomp:
2237       --     Disable Apple's precompiling preprocessor. It's a great thing
2238       --     for "normal" programs, but it doesn't support register variable
2239       --     declarations.
2240         = ( [], ["-no-cpp-precomp"] )
2241 #else
2242         = ( [], [] )
2243 #endif
2244
2245 picCCOpts :: DynFlags -> [String]
2246 picCCOpts _dflags
2247 #if darwin_TARGET_OS
2248       -- Apple prefers to do things the other way round.
2249       -- PIC is on by default.
2250       -- -mdynamic-no-pic:
2251       --     Turn off PIC code generation.
2252       -- -fno-common:
2253       --     Don't generate "common" symbols - these are unwanted
2254       --     in dynamic libraries.
2255
2256     | opt_PIC
2257         = ["-fno-common", "-U __PIC__","-D__PIC__"]
2258     | otherwise
2259         = ["-mdynamic-no-pic"]
2260 #elif mingw32_TARGET_OS
2261       -- no -fPIC for Windows
2262     | opt_PIC
2263         = ["-U __PIC__","-D__PIC__"]
2264     | otherwise
2265         = []
2266 #else
2267       -- we need -fPIC for C files when we are compiling with -dynamic,
2268       -- otherwise things like stub.c files don't get compiled
2269       -- correctly.  They need to reference data in the Haskell
2270       -- objects, but can't without -fPIC.  See
2271       -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode
2272     | opt_PIC || not opt_Static
2273         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
2274     | otherwise
2275         = []
2276 #endif
2277
2278 -- -----------------------------------------------------------------------------
2279 -- Splitting
2280
2281 can_split :: Bool
2282 can_split = cSplitObjs == "YES"
2283
2284 -- -----------------------------------------------------------------------------
2285 -- Compiler Info
2286
2287 data Printable = String String
2288                | FromDynFlags (DynFlags -> String)
2289
2290 compilerInfo :: [(String, Printable)]
2291 compilerInfo = [("Project name",                String cProjectName),
2292                 ("Project version",             String cProjectVersion),
2293                 ("Booter version",              String cBooterVersion),
2294                 ("Stage",                       String cStage),
2295                 ("Build platform",              String cBuildPlatformString),
2296                 ("Host platform",               String cHostPlatformString),
2297                 ("Target platform",             String cTargetPlatformString),
2298                 ("Have interpreter",            String cGhcWithInterpreter),
2299                 ("Object splitting",            String cSplitObjs),
2300                 ("Have native code generator",  String cGhcWithNativeCodeGen),
2301                 ("Support SMP",                 String cGhcWithSMP),
2302                 ("Unregisterised",              String cGhcUnregisterised),
2303                 ("Tables next to code",         String cGhcEnableTablesNextToCode),
2304                 ("RTS ways",                    String cGhcRTSWays),
2305                 ("Leading underscore",          String cLeadingUnderscore),
2306                 ("Debug on",                    String (show debugIsOn)),
2307                 ("LibDir",                      FromDynFlags topDir),
2308                 ("Global Package DB",           FromDynFlags systemPackageConfig),
2309                 ("C compiler flags",            String (show cCcOpts)),
2310                 ("Gcc Linker flags",            String (show cGccLinkerOpts)),
2311                 ("Ld Linker flags",             String (show cLdLinkerOpts))
2312                ]
2313