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