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