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