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