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