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