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