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