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