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