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