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