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