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