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