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