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