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