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