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