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