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