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