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