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