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