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