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