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