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