Comments only
[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
785 languageExtensions Nothing
786     -- Nothing => the default case
787     = Opt_MonoPatBinds   -- Experimentally, I'm making this non-standard
788                          -- behaviour the default, to see if anyone notices
789                          -- SLPJ July 06
790       -- In due course I'd like Opt_MonoLocalBinds to be on by default
791       -- But NB it's implied by GADTs etc
792       -- SLPJ September 2010
793     : languageExtensions (Just Haskell2010)
794
795 languageExtensions (Just Haskell98)
796     = [Opt_ImplicitPrelude,
797        Opt_MonomorphismRestriction,
798        Opt_NPlusKPatterns,
799        Opt_DatatypeContexts]
800
801 languageExtensions (Just Haskell2010)
802     = [Opt_ImplicitPrelude,
803        Opt_MonomorphismRestriction,
804        Opt_DatatypeContexts,
805        Opt_EmptyDataDecls,
806        Opt_ForeignFunctionInterface,
807        Opt_PatternGuards,
808        Opt_DoAndIfThenElse,
809        Opt_RelaxedPolyRec]
810
811 -- | Test whether a 'DynFlag' is set
812 dopt :: DynFlag -> DynFlags -> Bool
813 dopt f dflags  = f `elem` (flags dflags)
814
815 -- | Set a 'DynFlag'
816 dopt_set :: DynFlags -> DynFlag -> DynFlags
817 dopt_set dfs f = dfs{ flags = f : flags dfs }
818
819 -- | Unset a 'DynFlag'
820 dopt_unset :: DynFlags -> DynFlag -> DynFlags
821 dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
822
823 -- | Test whether a 'ExtensionFlag' is set
824 xopt :: ExtensionFlag -> DynFlags -> Bool
825 xopt f dflags = f `elem` extensionFlags dflags
826
827 -- | Set a 'ExtensionFlag'
828 xopt_set :: DynFlags -> ExtensionFlag -> DynFlags
829 xopt_set dfs f
830     = let onoffs = On f : extensions dfs
831       in dfs { extensions = onoffs,
832                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
833
834 -- | Unset a 'ExtensionFlag'
835 xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags
836 xopt_unset dfs f
837     = let onoffs = Off f : extensions dfs
838       in dfs { extensions = onoffs,
839                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
840
841 setLanguage :: Language -> DynP ()
842 setLanguage l = upd f
843     where f dfs = let mLang = Just l
844                       oneoffs = extensions dfs
845                   in dfs {
846                          language = mLang,
847                          extensionFlags = flattenExtensionFlags mLang oneoffs
848                      }
849
850 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
851 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
852         -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
853         -> [a]                  -- ^ Correctly ordered extracted options
854 getOpts dflags opts = reverse (opts dflags)
855         -- We add to the options from the front, so we need to reverse the list
856
857 -- | Gets the verbosity flag for the current verbosity level. This is fed to
858 -- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
859 getVerbFlag :: DynFlags -> String
860 getVerbFlag dflags
861   | verbosity dflags >= 3  = "-v"
862   | otherwise =  ""
863
864 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
865          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
866          setPgmP, addOptl, addOptP,
867          addCmdlineFramework, addHaddockOpts
868    :: String -> DynFlags -> DynFlags
869 setOutputFile, setOutputHi, setDumpPrefixForce
870    :: Maybe String -> DynFlags -> DynFlags
871
872 setObjectDir  f d = d{ objectDir  = Just f}
873 setHiDir      f d = d{ hiDir      = Just f}
874 setStubDir    f d = d{ stubDir    = Just f, includePaths = f : includePaths d }
875   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
876   -- \#included from the .hc file when compiling with -fvia-C.
877 setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
878 setDylibInstallName  f d = d{ dylibInstallName = Just f}
879
880 setObjectSuf  f d = d{ objectSuf  = f}
881 setHiSuf      f d = d{ hiSuf      = f}
882 setHcSuf      f d = d{ hcSuf      = f}
883
884 setOutputFile f d = d{ outputFile = f}
885 setOutputHi   f d = d{ outputHi   = f}
886
887 parseDynLibLoaderMode f d =
888  case splitAt 8 f of
889    ("deploy", "")       -> d{ dynLibLoader = Deployable }
890    ("sysdep", "")       -> d{ dynLibLoader = SystemDependent }
891    _                    -> ghcError (CmdLineError ("Unknown dynlib loader: " ++ f))
892
893 setDumpPrefixForce f d = d { dumpPrefixForce = f}
894
895 -- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
896 -- Config.hs should really use Option.
897 setPgmP   f d = let (pgm:args) = words f in d{ pgm_P   = (pgm, map Option args)}
898 addOptl   f d = d{ opt_l   = f : opt_l d}
899 addOptP   f d = d{ opt_P   = f : opt_P d}
900
901
902 setDepMakefile :: FilePath -> DynFlags -> DynFlags
903 setDepMakefile f d = d { depMakefile = deOptDep f }
904
905 setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
906 setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
907
908 addDepExcludeMod :: String -> DynFlags -> DynFlags
909 addDepExcludeMod m d
910     = d { depExcludeMods = mkModuleName (deOptDep m) : depExcludeMods d }
911
912 addDepSuffix :: FilePath -> DynFlags -> DynFlags
913 addDepSuffix s d = d { depSuffixes = deOptDep s : depSuffixes d }
914
915 -- XXX Legacy code:
916 -- We used to use "-optdep-flag -optdeparg", so for legacy applications
917 -- we need to strip the "-optdep" off of the arg
918 deOptDep :: String -> String
919 deOptDep x = case stripPrefix "-optdep" x of
920              Just rest -> rest
921              Nothing -> x
922
923 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
924
925 addHaddockOpts f d = d{ haddockOptions = Just f}
926
927 -- -----------------------------------------------------------------------------
928 -- Command-line options
929
930 -- | When invoking external tools as part of the compilation pipeline, we
931 -- pass these a sequence of options on the command-line. Rather than
932 -- just using a list of Strings, we use a type that allows us to distinguish
933 -- between filepaths and 'other stuff'. The reason for this is that
934 -- this type gives us a handle on transforming filenames, and filenames only,
935 -- to whatever format they're expected to be on a particular platform.
936 data Option
937  = FileOption -- an entry that _contains_ filename(s) / filepaths.
938               String  -- a non-filepath prefix that shouldn't be
939                       -- transformed (e.g., "/out=")
940               String  -- the filepath/filename portion
941  | Option     String
942
943 showOpt :: Option -> String
944 showOpt (FileOption pre f) = pre ++ f
945 showOpt (Option s)  = s
946
947 -----------------------------------------------------------------------------
948 -- Setting the optimisation level
949
950 updOptLevel :: Int -> DynFlags -> DynFlags
951 -- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
952 updOptLevel n dfs
953   = dfs2{ optLevel = final_n }
954   where
955    final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
956    dfs1 = foldr (flip dopt_unset) dfs  remove_dopts
957    dfs2 = foldr (flip dopt_set)   dfs1 extra_dopts
958
959    extra_dopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
960    remove_dopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
961
962 -- -----------------------------------------------------------------------------
963 -- StgToDo:  abstraction of stg-to-stg passes to run.
964
965 data StgToDo
966   = StgDoMassageForProfiling  -- should be (next to) last
967   -- There's also setStgVarInfo, but its absolute "lastness"
968   -- is so critical that it is hardwired in (no flag).
969   | D_stg_stats
970
971 getStgToDo :: DynFlags -> [StgToDo]
972 getStgToDo dflags
973   = todo2
974   where
975         stg_stats = dopt Opt_StgStats dflags
976
977         todo1 = if stg_stats then [D_stg_stats] else []
978
979         todo2 | WayProf `elem` wayNames dflags
980               = StgDoMassageForProfiling : todo1
981               | otherwise
982               = todo1
983
984 {- **********************************************************************
985 %*                                                                      *
986                 DynFlags parser
987 %*                                                                      *
988 %********************************************************************* -}
989
990 -- -----------------------------------------------------------------------------
991 -- Parsing the dynamic flags.
992
993 -- | Parse dynamic flags from a list of command line arguments.  Returns the
994 -- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
995 -- Throws a 'UsageError' if errors occurred during parsing (such as unknown
996 -- flags or missing arguments).
997 parseDynamicFlags :: Monad m =>
998                      DynFlags -> [Located String]
999                   -> m (DynFlags, [Located String], [Located String])
1000                      -- ^ Updated 'DynFlags', left-over arguments, and
1001                      -- list of warnings.
1002 parseDynamicFlags dflags args = parseDynamicFlags_ dflags args True
1003
1004 -- | Like 'parseDynamicFlags' but does not allow the package flags (-package,
1005 -- -hide-package, -ignore-package, -hide-all-packages, -package-conf).
1006 parseDynamicNoPackageFlags :: Monad m =>
1007                      DynFlags -> [Located String]
1008                   -> m (DynFlags, [Located String], [Located String])
1009                      -- ^ Updated 'DynFlags', left-over arguments, and
1010                      -- list of warnings.
1011 parseDynamicNoPackageFlags dflags args = parseDynamicFlags_ dflags args False
1012
1013 parseDynamicFlags_ :: Monad m =>
1014                       DynFlags -> [Located String] -> Bool
1015                   -> m (DynFlags, [Located String], [Located String])
1016 parseDynamicFlags_ dflags0 args pkg_flags = do
1017   -- XXX Legacy support code
1018   -- We used to accept things like
1019   --     optdep-f  -optdepdepend
1020   --     optdep-f  -optdep depend
1021   --     optdep -f -optdepdepend
1022   --     optdep -f -optdep depend
1023   -- but the spaces trip up proper argument handling. So get rid of them.
1024   let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs
1025       f (x : xs) = x : f xs
1026       f xs = xs
1027       args' = f args
1028
1029       -- Note: -ignore-package (package_flags) must precede -i* (dynamic_flags)
1030       flag_spec | pkg_flags = package_flags ++ dynamic_flags
1031                 | otherwise = dynamic_flags
1032
1033   let ((leftover, errs, warns), dflags1)
1034           = runCmdLine (processArgs flag_spec args') dflags0
1035   when (not (null errs)) $ ghcError $ errorsToGhcException errs
1036
1037   -- Cannot use -fPIC with registerised -fvia-C, because the mangler
1038   -- isn't up to the job.  We know that if hscTarget == HscC, then the
1039   -- user has explicitly used -fvia-C, because -fasm is the default,
1040   -- unless there is no NCG on this platform.  The latter case is
1041   -- checked when the -fPIC flag is parsed.
1042   --
1043   let (pic_warns, dflags2)
1044         | opt_PIC && hscTarget dflags1 == HscC && cGhcUnregisterised == "NO"
1045         = ([L noSrcSpan $ "Warning: -fvia-C is incompatible with -fPIC; ignoring -fvia-C"],
1046                 dflags1{ hscTarget = HscAsm })
1047 #if !(x86_64_TARGET_ARCH && linux_TARGET_OS)
1048         | (not opt_Static || opt_PIC) && hscTarget dflags1 == HscLlvm
1049         = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and -"
1050                 ++ "dynamic on this platform;\n              ignoring -fllvm"],
1051                 dflags1{ hscTarget = HscAsm })
1052 #endif
1053         | otherwise = ([], dflags1)
1054
1055   return (dflags2, leftover, pic_warns ++ warns)
1056
1057
1058 {- **********************************************************************
1059 %*                                                                      *
1060                 DynFlags specifications
1061 %*                                                                      *
1062 %********************************************************************* -}
1063
1064 allFlags :: [String]
1065 allFlags = map ('-':) $
1066            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
1067            map ("fno-"++) flags ++
1068            map ("f"++) flags ++
1069            map ("f"++) flags' ++
1070            map ("X"++) supportedExtensions
1071     where ok (PrefixPred _ _) = False
1072           ok _ = True
1073           flags = [ name | (name, _, _) <- fFlags ]
1074           flags' = [ name | (name, _, _) <- fLangFlags ]
1075
1076 --------------- The main flags themselves ------------------
1077 dynamic_flags :: [Flag (CmdLineP DynFlags)]
1078 dynamic_flags = [
1079     Flag "n"        (NoArg (setDynFlag Opt_DryRun))
1080   , Flag "cpp"      (NoArg (setExtensionFlag Opt_Cpp)) 
1081   , Flag "F"        (NoArg (setDynFlag Opt_Pp)) 
1082   , Flag "#include" 
1083          (HasArg (\s -> do { addCmdlineHCInclude s
1084                            ; addWarn "-#include and INCLUDE pragmas are deprecated: They no longer have any effect" }))
1085   , Flag "v"        (OptIntSuffix setVerbosity)
1086
1087         ------- Specific phases  --------------------------------------------
1088     -- need to appear before -pgmL to be parsed as LLVM flags.
1089   , Flag "pgmlo"          (hasArg (\f d -> d{ pgm_lo  = (f,[])}))
1090   , Flag "pgmlc"          (hasArg (\f d -> d{ pgm_lc  = (f,[])}))
1091   , Flag "pgmL"           (hasArg (\f d -> d{ pgm_L   = f}))
1092   , Flag "pgmP"           (hasArg setPgmP)
1093   , Flag "pgmF"           (hasArg (\f d -> d{ pgm_F   = f}))
1094   , Flag "pgmc"           (hasArg (\f d -> d{ pgm_c   = (f,[])}))
1095   , Flag "pgmm"           (hasArg (\f d -> d{ pgm_m   = (f,[])}))
1096   , Flag "pgms"           (hasArg (\f d -> d{ pgm_s   = (f,[])}))
1097   , Flag "pgma"           (hasArg (\f d -> d{ pgm_a   = (f,[])}))
1098   , Flag "pgml"           (hasArg (\f d -> d{ pgm_l   = (f,[])}))
1099   , Flag "pgmdll"         (hasArg (\f d -> d{ pgm_dll = (f,[])}))
1100   , Flag "pgmwindres"     (hasArg (\f d -> d{ pgm_windres = f}))
1101
1102     -- need to appear before -optl/-opta to be parsed as LLVM flags.
1103   , Flag "optlo"          (hasArg (\f d -> d{ opt_lo  = f : opt_lo d}))
1104   , Flag "optlc"          (hasArg (\f d -> d{ opt_lc  = f : opt_lc d}))
1105   , Flag "optL"           (hasArg (\f d -> d{ opt_L   = f : opt_L d}))
1106   , Flag "optP"           (hasArg addOptP)
1107   , Flag "optF"           (hasArg (\f d -> d{ opt_F   = f : opt_F d}))
1108   , Flag "optc"           (hasArg (\f d -> d{ opt_c   = f : opt_c d}))
1109   , Flag "optm"           (hasArg (\f d -> d{ opt_m   = f : opt_m d}))
1110   , Flag "opta"           (hasArg (\f d -> d{ opt_a   = f : opt_a d}))
1111   , Flag "optl"           (hasArg addOptl)
1112   , Flag "optwindres"     (hasArg (\f d -> d{ opt_windres = f : opt_windres d}))
1113
1114   , Flag "split-objs"
1115          (NoArg (if can_split 
1116                  then setDynFlag Opt_SplitObjs
1117                  else addWarn "ignoring -fsplit-objs"))
1118
1119         -------- ghc -M -----------------------------------------------------
1120   , Flag "dep-suffix"     (hasArg addDepSuffix)
1121   , Flag "optdep-s"       (hasArgDF addDepSuffix "Use -dep-suffix instead")
1122   , Flag "dep-makefile"   (hasArg setDepMakefile)
1123   , Flag "optdep-f"       (hasArgDF setDepMakefile "Use -dep-makefile instead")
1124   , Flag "optdep-w"       (NoArg  (deprecate "doesn't do anything"))
1125   , Flag "include-pkg-deps"         (noArg (setDepIncludePkgDeps True))
1126   , Flag "optdep--include-prelude"  (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
1127   , Flag "optdep--include-pkg-deps" (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
1128   , Flag "exclude-module"           (hasArg addDepExcludeMod)
1129   , Flag "optdep--exclude-module"   (hasArgDF addDepExcludeMod "Use -exclude-module instead")
1130   , Flag "optdep-x"                 (hasArgDF addDepExcludeMod "Use -exclude-module instead")
1131
1132         -------- Linking ----------------------------------------------------
1133   , Flag "no-link"            (noArg (\d -> d{ ghcLink=NoLink }))
1134   , Flag "shared"             (noArg (\d -> d{ ghcLink=LinkDynLib }))
1135   , Flag "dynload"            (hasArg parseDynLibLoaderMode)
1136   , Flag "dylib-install-name" (hasArg setDylibInstallName)
1137
1138         ------- Libraries ---------------------------------------------------
1139   , Flag "L"   (Prefix    addLibraryPath)
1140   , Flag "l"   (AnySuffix (upd . addOptl))
1141
1142         ------- Frameworks --------------------------------------------------
1143         -- -framework-path should really be -F ...
1144   , Flag "framework-path" (HasArg addFrameworkPath)
1145   , Flag "framework"      (hasArg addCmdlineFramework)
1146
1147         ------- Output Redirection ------------------------------------------
1148   , Flag "odir"              (hasArg setObjectDir)
1149   , Flag "o"                 (SepArg (upd . setOutputFile . Just))
1150   , Flag "ohi"               (hasArg (setOutputHi . Just ))
1151   , Flag "osuf"              (hasArg setObjectSuf)
1152   , Flag "hcsuf"             (hasArg setHcSuf)
1153   , Flag "hisuf"             (hasArg setHiSuf)
1154   , Flag "hidir"             (hasArg setHiDir)
1155   , Flag "tmpdir"            (hasArg setTmpDir)
1156   , Flag "stubdir"           (hasArg setStubDir)
1157   , Flag "outputdir"         (hasArg setOutputDir)
1158   , Flag "ddump-file-prefix" (hasArg (setDumpPrefixForce . Just))
1159
1160         ------- Keeping temporary files -------------------------------------
1161      -- These can be singular (think ghc -c) or plural (think ghc --make)
1162   , Flag "keep-hc-file"     (NoArg (setDynFlag Opt_KeepHcFiles))
1163   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles))
1164   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles))
1165   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles))
1166   , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles))
1167   , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles))
1168   , Flag "keep-llvm-file"   (NoArg (setDynFlag Opt_KeepLlvmFiles))
1169   , Flag "keep-llvm-files"  (NoArg (setDynFlag Opt_KeepLlvmFiles))
1170      -- This only makes sense as plural
1171   , Flag "keep-tmp-files"   (NoArg (setDynFlag Opt_KeepTmpFiles))
1172
1173         ------- Miscellaneous ----------------------------------------------
1174   , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages))
1175   , Flag "no-hs-main"     (NoArg (setDynFlag Opt_NoHsMain))
1176   , Flag "with-rtsopts"   (HasArg setRtsOpts)
1177   , Flag "rtsopts"        (NoArg (setRtsOptsEnabled RtsOptsAll))
1178   , Flag "rtsopts=all"    (NoArg (setRtsOptsEnabled RtsOptsAll))
1179   , Flag "rtsopts=some"   (NoArg (setRtsOptsEnabled RtsOptsSafeOnly))
1180   , Flag "rtsopts=none"   (NoArg (setRtsOptsEnabled RtsOptsNone))
1181   , Flag "no-rtsopts"     (NoArg (setRtsOptsEnabled RtsOptsNone))
1182   , Flag "main-is"        (SepArg setMainIs)
1183   , Flag "haddock"        (NoArg (setDynFlag Opt_Haddock))
1184   , Flag "haddock-opts"   (hasArg addHaddockOpts)
1185   , Flag "hpcdir"         (SepArg setOptHpcDir)
1186
1187         ------- recompilation checker --------------------------------------
1188   , Flag "recomp"         (NoArg (do { unSetDynFlag Opt_ForceRecomp
1189                                      ; deprecate "Use -fno-force-recomp instead" }))
1190   , Flag "no-recomp"      (NoArg (do { setDynFlag Opt_ForceRecomp
1191                                      ; deprecate "Use -fforce-recomp instead" }))
1192
1193         ------ HsCpp opts ---------------------------------------------------
1194   , Flag "D"              (AnySuffix (upd . addOptP))
1195   , Flag "U"              (AnySuffix (upd . addOptP))
1196
1197         ------- Include/Import Paths ----------------------------------------
1198   , Flag "I"              (Prefix    addIncludePath)
1199   , Flag "i"              (OptPrefix addImportPath)
1200
1201         ------ Debugging ----------------------------------------------------
1202   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats))
1203
1204   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
1205   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
1206   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
1207   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
1208   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
1209   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
1210   , Flag "ddump-asm-native"        (setDumpFlag Opt_D_dump_asm_native)
1211   , Flag "ddump-asm-liveness"      (setDumpFlag Opt_D_dump_asm_liveness)
1212   , Flag "ddump-asm-coalesce"      (setDumpFlag Opt_D_dump_asm_coalesce)
1213   , Flag "ddump-asm-regalloc"      (setDumpFlag Opt_D_dump_asm_regalloc)
1214   , Flag "ddump-asm-conflicts"     (setDumpFlag Opt_D_dump_asm_conflicts)
1215   , Flag "ddump-asm-regalloc-stages" (setDumpFlag Opt_D_dump_asm_regalloc_stages)
1216   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
1217   , Flag "ddump-asm-expanded"      (setDumpFlag Opt_D_dump_asm_expanded)
1218   , Flag "ddump-llvm"              (NoArg (do { setObjTarget HscLlvm
1219                                               ; setDumpFlag' Opt_D_dump_llvm}))
1220   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
1221   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
1222   , Flag "ddump-ds"                (setDumpFlag Opt_D_dump_ds)
1223   , Flag "ddump-flatC"             (setDumpFlag Opt_D_dump_flatC)
1224   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
1225   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
1226   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
1227   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
1228   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
1229   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
1230   , Flag "ddump-simpl"             (setDumpFlag Opt_D_dump_simpl)
1231   , Flag "ddump-simpl-iterations"  (setDumpFlag Opt_D_dump_simpl_iterations)
1232   , Flag "ddump-simpl-phases"      (OptPrefix setDumpSimplPhases)
1233   , Flag "ddump-spec"              (setDumpFlag Opt_D_dump_spec)
1234   , Flag "ddump-prep"              (setDumpFlag Opt_D_dump_prep)
1235   , Flag "ddump-stg"               (setDumpFlag Opt_D_dump_stg)
1236   , Flag "ddump-stranal"           (setDumpFlag Opt_D_dump_stranal)
1237   , Flag "ddump-tc"                (setDumpFlag Opt_D_dump_tc)
1238   , Flag "ddump-types"             (setDumpFlag Opt_D_dump_types)
1239   , Flag "ddump-rules"             (setDumpFlag Opt_D_dump_rules)
1240   , Flag "ddump-cse"               (setDumpFlag Opt_D_dump_cse)
1241   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
1242   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
1243   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
1244   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
1245   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
1246   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
1247   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
1248   , Flag "ddump-simpl-stats"       (setDumpFlag Opt_D_dump_simpl_stats)
1249   , Flag "ddump-bcos"              (setDumpFlag Opt_D_dump_BCOs)
1250   , Flag "dsource-stats"           (setDumpFlag Opt_D_source_stats)
1251   , Flag "dverbose-core2core"      (NoArg (do { setVerbosity (Just 2)
1252                                               ; setVerboseCore2Core }))
1253   , Flag "dverbose-stg2stg"        (setDumpFlag Opt_D_verbose_stg2stg)
1254   , Flag "ddump-hi"                (setDumpFlag Opt_D_dump_hi)
1255   , Flag "ddump-minimal-imports"   (setDumpFlag Opt_D_dump_minimal_imports)
1256   , Flag "ddump-vect"              (setDumpFlag Opt_D_dump_vect)
1257   , Flag "ddump-hpc"               (setDumpFlag Opt_D_dump_hpc)
1258   , Flag "ddump-mod-cycles"        (setDumpFlag Opt_D_dump_mod_cycles)
1259   , Flag "ddump-view-pattern-commoning" (setDumpFlag Opt_D_dump_view_pattern_commoning)
1260   , Flag "ddump-to-file"           (setDumpFlag Opt_DumpToFile)
1261   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
1262   , Flag "ddump-rtti"              (setDumpFlag Opt_D_dump_rtti)
1263   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
1264   , Flag "dstg-lint"               (NoArg (setDynFlag Opt_DoStgLinting))
1265   , Flag "dcmm-lint"               (NoArg (setDynFlag Opt_DoCmmLinting))
1266   , Flag "dasm-lint"               (NoArg (setDynFlag Opt_DoAsmLinting))
1267   , Flag "dshow-passes"            (NoArg (do forceRecompile
1268                                               setVerbosity (Just 2)))
1269   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
1270
1271         ------ Machine dependant (-m<blah>) stuff ---------------------------
1272
1273   , Flag "monly-2-regs" (noArg (\s -> s{stolen_x86_regs = 2}))
1274   , Flag "monly-3-regs" (noArg (\s -> s{stolen_x86_regs = 3}))
1275   , Flag "monly-4-regs" (noArg (\s -> s{stolen_x86_regs = 4}))
1276   , Flag "msse2"        (NoArg (setDynFlag Opt_SSE2))
1277
1278      ------ Warning opts -------------------------------------------------
1279   , Flag "W"      (NoArg (mapM_ setDynFlag   minusWOpts))
1280   , Flag "Werror" (NoArg (setDynFlag         Opt_WarnIsError))
1281   , Flag "Wwarn"  (NoArg (unSetDynFlag       Opt_WarnIsError))
1282   , Flag "Wall"   (NoArg (mapM_ setDynFlag   minusWallOpts))
1283   , Flag "Wnot"   (NoArg (do { mapM_ unSetDynFlag minusWallOpts
1284                              ; deprecate "Use -w instead" }))
1285   , Flag "w"      (NoArg (mapM_ unSetDynFlag minuswRemovesOpts))
1286
1287         ------ Optimisation flags ------------------------------------------
1288   , Flag "O"      (noArg (setOptLevel 1))
1289   , Flag "Onot"   (noArgDF (setOptLevel 0) "Use -O0 instead")
1290   , Flag "Odph"   (noArg setDPHOpt)
1291   , Flag "O"      (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1292                 -- If the number is missing, use 1
1293
1294   , Flag "fsimplifier-phases"          (intSuffix (\n d -> d{ simplPhases = n }))
1295   , Flag "fmax-simplifier-iterations"  (intSuffix (\n d -> d{ maxSimplIterations = n }))
1296   , Flag "fspec-constr-threshold"      (intSuffix (\n d -> d{ specConstrThreshold = Just n }))
1297   , Flag "fno-spec-constr-threshold"   (noArg (\d -> d{ specConstrThreshold = Nothing }))
1298   , Flag "fspec-constr-count"          (intSuffix (\n d -> d{ specConstrCount = Just n }))
1299   , Flag "fno-spec-constr-count"       (noArg (\d -> d{ specConstrCount = Nothing }))
1300   , Flag "fliberate-case-threshold"    (intSuffix (\n d -> d{ liberateCaseThreshold = Just n }))
1301   , Flag "fno-liberate-case-threshold" (noArg (\d -> d{ liberateCaseThreshold = Nothing }))
1302   , Flag "frule-check"                 (SepArg (\s -> upd (\d -> d{ ruleCheck = Just s })))
1303   , Flag "fcontext-stack"              (intSuffix (\n d -> d{ ctxtStkDepth = n }))
1304   , Flag "fstrictness-before"          (intSuffix (\n d -> d{ strictnessBefore = n : strictnessBefore d }))
1305
1306         ------ Profiling ----------------------------------------------------
1307
1308   -- XXX Should the -f* flags be deprecated?
1309   -- They don't seem to be documented
1310   , Flag "fauto-sccs-on-all-toplevs"       (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1311   , Flag "auto-all"                        (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
1312   , Flag "no-auto-all"                     (NoArg (unSetDynFlag Opt_AutoSccsOnAllToplevs))
1313   , Flag "fauto-sccs-on-exported-toplevs"  (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1314   , Flag "auto"                            (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
1315   , Flag "no-auto"                         (NoArg (unSetDynFlag Opt_AutoSccsOnExportedToplevs))
1316   , Flag "fauto-sccs-on-individual-cafs"   (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1317   , Flag "caf-all"                         (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
1318   , Flag "no-caf-all"                      (NoArg (unSetDynFlag Opt_AutoSccsOnIndividualCafs))
1319
1320         ------ DPH flags ----------------------------------------------------
1321
1322   , Flag "fdph-seq"         (NoArg (setDPHBackend DPHSeq))
1323   , Flag "fdph-par"         (NoArg (setDPHBackend DPHPar))
1324   , Flag "fdph-this"        (NoArg (setDPHBackend DPHThis))
1325
1326         ------ Compiler flags -----------------------------------------------
1327
1328   , Flag "fasm"             (NoArg (setObjTarget HscAsm))
1329   , Flag "fvia-c"           (NoArg (setObjTarget HscC >>
1330          (addWarn "The -fvia-c flag will be removed in a future GHC release")))
1331   , Flag "fvia-C"           (NoArg (setObjTarget HscC >>
1332          (addWarn "The -fvia-C flag will be removed in a future GHC release")))
1333   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm))
1334
1335   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
1336                                        setTarget HscNothing))
1337   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted))
1338   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget))
1339   , Flag "fglasgow-exts"    (NoArg (enableGlasgowExts >> deprecate "Use individual extensions instead"))
1340   , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use individual extensions instead"))
1341  ]
1342  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
1343  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
1344  ++ map (mkFlag True  "f"    setExtensionFlag  ) fLangFlags
1345  ++ map (mkFlag False "fno-" unSetExtensionFlag) fLangFlags
1346  ++ map (mkFlag True  "X"    setExtensionFlag  ) xFlags
1347  ++ map (mkFlag False "XNo"  unSetExtensionFlag) xFlags
1348  ++ map (mkFlag True  "X"    setLanguage) languageFlags
1349
1350 package_flags :: [Flag (CmdLineP DynFlags)]
1351 package_flags = [
1352         ------- Packages ----------------------------------------------------
1353     Flag "package-conf"         (HasArg extraPkgConf_)
1354   , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
1355   , Flag "package-name"         (hasArg setPackageName)
1356   , Flag "package-id"           (HasArg exposePackageId)
1357   , Flag "package"              (HasArg exposePackage)
1358   , Flag "hide-package"         (HasArg hidePackage)
1359   , Flag "hide-all-packages"    (NoArg (setDynFlag Opt_HideAllPackages))
1360   , Flag "ignore-package"       (HasArg ignorePackage)
1361   , Flag "syslib"               (HasArg (\s -> do { exposePackage s
1362                                                   ; deprecate "Use -package instead" }))
1363   ]
1364
1365 type FlagSpec flag 
1366    = ( String   -- Flag in string form
1367      , flag     -- Flag in internal form
1368      , Bool -> DynP ())  -- Extra action to run when the flag is found
1369                          -- Typically, emit a warning or error
1370                          -- True  <=> we are turning the flag on
1371                          -- False <=> we are turning the flag off
1372
1373
1374 mkFlag :: Bool                  -- ^ True <=> it should be turned on
1375        -> String                -- ^ The flag prefix
1376        -> (flag -> DynP ())     -- ^ What to do when the flag is found
1377        -> FlagSpec flag         -- ^ Specification of this particular flag
1378        -> Flag (CmdLineP DynFlags)
1379 mkFlag turnOn flagPrefix f (name, flag, extra_action)
1380     = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turnOn))
1381
1382 deprecatedForExtension :: String -> Bool -> DynP ()
1383 deprecatedForExtension lang turn_on
1384     = deprecate ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead")
1385     where 
1386       flag | turn_on    = lang
1387            | otherwise = "No"++lang
1388
1389 useInstead :: String -> Bool -> DynP ()
1390 useInstead flag turn_on
1391   = deprecate ("Use -f" ++ no ++ flag ++ " instead")
1392   where
1393     no = if turn_on then "" else "no-"
1394
1395 nop :: Bool -> DynP ()
1396 nop _ = return ()
1397
1398 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1399 fFlags :: [FlagSpec DynFlag]
1400 fFlags = [
1401   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, nop ),
1402   ( "warn-dodgy-exports",               Opt_WarnDodgyExports, nop ),
1403   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, nop ),
1404   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, nop ),
1405   ( "warn-hi-shadowing",                Opt_WarnHiShadows, nop ),
1406   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, nop ),
1407   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, nop ),
1408   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, nop ),
1409   ( "warn-missing-fields",              Opt_WarnMissingFields, nop ),
1410   ( "warn-missing-import-lists",        Opt_WarnMissingImportList, nop ),
1411   ( "warn-missing-methods",             Opt_WarnMissingMethods, nop ),
1412   ( "warn-missing-signatures",          Opt_WarnMissingSigs, nop ),
1413   ( "warn-missing-local-sigs",          Opt_WarnMissingLocalSigs, nop ),
1414   ( "warn-name-shadowing",              Opt_WarnNameShadowing, nop ),
1415   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns, nop ),
1416   ( "warn-type-defaults",               Opt_WarnTypeDefaults, nop ),
1417   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism, nop ),
1418   ( "warn-unused-binds",                Opt_WarnUnusedBinds, nop ),
1419   ( "warn-unused-imports",              Opt_WarnUnusedImports, nop ),
1420   ( "warn-unused-matches",              Opt_WarnUnusedMatches, nop ),
1421   ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, nop ),
1422   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, nop ),
1423   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, nop ),
1424   ( "warn-orphans",                     Opt_WarnOrphans, nop ),
1425   ( "warn-auto-orphans",                Opt_WarnAutoOrphans, nop ),
1426   ( "warn-tabs",                        Opt_WarnTabs, nop ),
1427   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, nop ),
1428   ( "warn-lazy-unlifted-bindings",      Opt_WarnLazyUnliftedBindings, nop),
1429   ( "warn-unused-do-bind",              Opt_WarnUnusedDoBind, nop ),
1430   ( "warn-wrong-do-bind",               Opt_WarnWrongDoBind, nop ),
1431   ( "warn-alternative-layout-rule-transitional", Opt_WarnAlternativeLayoutRuleTransitional, nop ),
1432   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, nop ),
1433   ( "strictness",                       Opt_Strictness, nop ),
1434   ( "specialise",                       Opt_Specialise, nop ),
1435   ( "float-in",                         Opt_FloatIn, nop ),
1436   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, nop ),
1437   ( "full-laziness",                    Opt_FullLaziness, nop ),
1438   ( "liberate-case",                    Opt_LiberateCase, nop ),
1439   ( "spec-constr",                      Opt_SpecConstr, nop ),
1440   ( "cse",                              Opt_CSE, nop ),
1441   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas, nop ),
1442   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas, nop ),
1443   ( "expose-all-unfoldings",            Opt_ExposeAllUnfoldings, nop ),
1444   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion, nop ),
1445   ( "ignore-asserts",                   Opt_IgnoreAsserts, nop ),
1446   ( "do-eta-reduction",                 Opt_DoEtaReduction, nop ),
1447   ( "case-merge",                       Opt_CaseMerge, nop ),
1448   ( "unbox-strict-fields",              Opt_UnboxStrictFields, nop ),
1449   ( "method-sharing",                   Opt_MethodSharing, nop ),
1450   ( "dicts-cheap",                      Opt_DictsCheap, nop ),
1451   ( "excess-precision",                 Opt_ExcessPrecision, nop ),
1452   ( "eager-blackholing",                Opt_EagerBlackHoling, nop ),
1453   ( "asm-mangling",                     Opt_DoAsmMangling, nop ),
1454   ( "print-bind-result",                Opt_PrintBindResult, nop ),
1455   ( "force-recomp",                     Opt_ForceRecomp, nop ),
1456   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, nop ),
1457   ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
1458   ( "enable-rewrite-rules",             Opt_EnableRewriteRules, nop ),
1459   ( "break-on-exception",               Opt_BreakOnException, nop ),
1460   ( "break-on-error",                   Opt_BreakOnError, nop ),
1461   ( "print-evld-with-show",             Opt_PrintEvldWithShow, nop ),
1462   ( "print-bind-contents",              Opt_PrintBindContents, nop ),
1463   ( "run-cps",                          Opt_RunCPS, nop ),
1464   ( "run-cpsz",                         Opt_RunCPSZ, nop ),
1465   ( "new-codegen",                      Opt_TryNewCodeGen, nop ),
1466   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, nop ),
1467   ( "vectorise",                        Opt_Vectorise, nop ),
1468   ( "regs-graph",                       Opt_RegsGraph, nop ),
1469   ( "regs-iterative",                   Opt_RegsIterative, nop ),
1470   ( "gen-manifest",                     Opt_GenManifest, nop ),
1471   ( "embed-manifest",                   Opt_EmbedManifest, nop ),
1472   ( "ext-core",                         Opt_EmitExternalCore, nop ),
1473   ( "shared-implib",                    Opt_SharedImplib, nop ),
1474   ( "ghci-sandbox",                     Opt_GhciSandbox, nop ),
1475   ( "building-cabal-package",           Opt_BuildingCabalPackage, nop ),
1476   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, nop )
1477   ]
1478
1479 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
1480 fLangFlags :: [FlagSpec ExtensionFlag]
1481 fLangFlags = [
1482   ( "th",                               Opt_TemplateHaskell,
1483     deprecatedForExtension "TemplateHaskell" >> checkTemplateHaskellOk ),
1484   ( "fi",                               Opt_ForeignFunctionInterface,
1485     deprecatedForExtension "ForeignFunctionInterface" ),
1486   ( "ffi",                              Opt_ForeignFunctionInterface,
1487     deprecatedForExtension "ForeignFunctionInterface" ),
1488   ( "arrows",                           Opt_Arrows,
1489     deprecatedForExtension "Arrows" ),
1490   ( "generics",                         Opt_Generics,
1491     deprecatedForExtension "Generics" ),
1492   ( "implicit-prelude",                 Opt_ImplicitPrelude,
1493     deprecatedForExtension "ImplicitPrelude" ),
1494   ( "bang-patterns",                    Opt_BangPatterns,
1495     deprecatedForExtension "BangPatterns" ),
1496   ( "monomorphism-restriction",         Opt_MonomorphismRestriction,
1497     deprecatedForExtension "MonomorphismRestriction" ),
1498   ( "mono-pat-binds",                   Opt_MonoPatBinds,
1499     deprecatedForExtension "MonoPatBinds" ),
1500   ( "extended-default-rules",           Opt_ExtendedDefaultRules,
1501     deprecatedForExtension "ExtendedDefaultRules" ),
1502   ( "implicit-params",                  Opt_ImplicitParams,
1503     deprecatedForExtension "ImplicitParams" ),
1504   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
1505     deprecatedForExtension "ScopedTypeVariables" ),
1506   ( "parr",                             Opt_PArr,
1507     deprecatedForExtension "PArr" ),
1508   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
1509     deprecatedForExtension "OverlappingInstances" ),
1510   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
1511     deprecatedForExtension "UndecidableInstances" ),
1512   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
1513     deprecatedForExtension "IncoherentInstances" )
1514   ]
1515
1516 supportedLanguages :: [String]
1517 supportedLanguages = [ name | (name, _, _) <- languageFlags ]
1518
1519 supportedExtensions :: [String]
1520 supportedExtensions = [ name' | (name, _, _) <- xFlags, name' <- [name, "No" ++ name] ]
1521
1522 supportedLanguagesAndExtensions :: [String]
1523 supportedLanguagesAndExtensions = supportedLanguages ++ supportedExtensions
1524
1525 -- | These -X<blah> flags cannot be reversed with -XNo<blah>
1526 languageFlags :: [FlagSpec Language]
1527 languageFlags = [
1528   ( "Haskell98",                        Haskell98, nop ),
1529   ( "Haskell2010",                      Haskell2010, nop )
1530   ]
1531
1532 -- | These -X<blah> flags can all be reversed with -XNo<blah>
1533 xFlags :: [FlagSpec ExtensionFlag]
1534 xFlags = [
1535   ( "CPP",                              Opt_Cpp, nop ),
1536   ( "PostfixOperators",                 Opt_PostfixOperators, nop ),
1537   ( "TupleSections",                    Opt_TupleSections, nop ),
1538   ( "PatternGuards",                    Opt_PatternGuards, nop ),
1539   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, nop ),
1540   ( "MagicHash",                        Opt_MagicHash, nop ),
1541   ( "PolymorphicComponents",            Opt_PolymorphicComponents, nop ),
1542   ( "ExistentialQuantification",        Opt_ExistentialQuantification, nop ),
1543   ( "KindSignatures",                   Opt_KindSignatures, nop ),
1544   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, nop ),
1545   ( "ParallelListComp",                 Opt_ParallelListComp, nop ),
1546   ( "TransformListComp",                Opt_TransformListComp, nop ),
1547   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, nop ),
1548   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, nop ),
1549   ( "GHCForeignImportPrim",             Opt_GHCForeignImportPrim, nop ),
1550   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, nop ),
1551   ( "Rank2Types",                       Opt_Rank2Types, nop ),
1552   ( "RankNTypes",                       Opt_RankNTypes, nop ),
1553   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, nop), 
1554   ( "TypeOperators",                    Opt_TypeOperators, nop ),
1555   ( "RecursiveDo",                      Opt_RecursiveDo,
1556     deprecatedForExtension "DoRec"),
1557   ( "DoRec",                            Opt_DoRec, nop ),
1558   ( "Arrows",                           Opt_Arrows, nop ),
1559   ( "PArr",                             Opt_PArr, nop ),
1560   ( "TemplateHaskell",                  Opt_TemplateHaskell, checkTemplateHaskellOk ),
1561   ( "QuasiQuotes",                      Opt_QuasiQuotes, nop ),
1562   ( "Generics",                         Opt_Generics, nop ),
1563   ( "ImplicitPrelude",                  Opt_ImplicitPrelude, nop ),
1564   ( "RecordWildCards",                  Opt_RecordWildCards, nop ),
1565   ( "NamedFieldPuns",                   Opt_RecordPuns, nop ),
1566   ( "RecordPuns",                       Opt_RecordPuns,
1567     deprecatedForExtension "NamedFieldPuns" ),
1568   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, nop ),
1569   ( "OverloadedStrings",                Opt_OverloadedStrings, nop ),
1570   ( "GADTs",                            Opt_GADTs, nop ),
1571   ( "ViewPatterns",                     Opt_ViewPatterns, nop ),
1572   ( "TypeFamilies",                     Opt_TypeFamilies, nop ),
1573   ( "BangPatterns",                     Opt_BangPatterns, nop ),
1574   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, nop ),
1575   ( "NPlusKPatterns",                   Opt_NPlusKPatterns, nop ),
1576   ( "DoAndIfThenElse",                  Opt_DoAndIfThenElse, nop ),
1577   ( "RebindableSyntax",                 Opt_RebindableSyntax, nop ),
1578   ( "MonoPatBinds",                     Opt_MonoPatBinds, nop ),
1579   ( "ExplicitForAll",                   Opt_ExplicitForAll, nop ),
1580   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, nop ),
1581   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, nop ),
1582   ( "DatatypeContexts",                 Opt_DatatypeContexts, nop ),
1583   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, nop ),
1584   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, 
1585     \ turn_on -> if not turn_on 
1586                  then deprecate "You can't turn off RelaxedPolyRec any more"
1587                  else return () ),
1588   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, nop ),
1589   ( "ImplicitParams",                   Opt_ImplicitParams, nop ),
1590   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, nop ),
1591
1592   ( "PatternSignatures",                Opt_ScopedTypeVariables, 
1593     deprecatedForExtension "ScopedTypeVariables" ),
1594
1595   ( "UnboxedTuples",                    Opt_UnboxedTuples, nop ),
1596   ( "StandaloneDeriving",               Opt_StandaloneDeriving, nop ),
1597   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, nop ),
1598   ( "DeriveFunctor",                    Opt_DeriveFunctor, nop ),
1599   ( "DeriveTraversable",                Opt_DeriveTraversable, nop ),
1600   ( "DeriveFoldable",                   Opt_DeriveFoldable, nop ),
1601   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, nop ),
1602   ( "FlexibleContexts",                 Opt_FlexibleContexts, nop ),
1603   ( "FlexibleInstances",                Opt_FlexibleInstances, nop ),
1604   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods, nop ),
1605   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses, nop ),
1606   ( "FunctionalDependencies",           Opt_FunctionalDependencies, nop ),
1607   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, nop ),
1608   ( "OverlappingInstances",             Opt_OverlappingInstances, nop ),
1609   ( "UndecidableInstances",             Opt_UndecidableInstances, nop ),
1610   ( "IncoherentInstances",              Opt_IncoherentInstances, nop ),
1611   ( "PackageImports",                   Opt_PackageImports, nop ),
1612   ( "NewQualifiedOperators",            Opt_NewQualifiedOperators,
1613     \_ -> deprecate "The new qualified operator syntax was rejected by Haskell'" )
1614   ]
1615
1616 defaultFlags :: [DynFlag]
1617 defaultFlags 
1618   = [ Opt_AutoLinkPackages,
1619       Opt_ReadUserPackageConf,
1620
1621       Opt_MethodSharing,
1622
1623       Opt_DoAsmMangling,
1624
1625       Opt_SharedImplib,
1626
1627       Opt_GenManifest,
1628       Opt_EmbedManifest,
1629       Opt_PrintBindContents,
1630       Opt_GhciSandbox
1631     ]
1632
1633     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
1634              -- The default -O0 options
1635
1636     ++ standardWarnings
1637
1638 impliedFlags :: [(ExtensionFlag, ExtensionFlag)]
1639 impliedFlags
1640   = [ (Opt_RankNTypes,                Opt_ExplicitForAll)
1641     , (Opt_Rank2Types,                Opt_ExplicitForAll)
1642     , (Opt_ScopedTypeVariables,       Opt_ExplicitForAll)
1643     , (Opt_LiberalTypeSynonyms,       Opt_ExplicitForAll)
1644     , (Opt_ExistentialQuantification, Opt_ExplicitForAll)
1645     , (Opt_PolymorphicComponents,     Opt_ExplicitForAll)
1646
1647     , (Opt_RebindableSyntax,          Opt_ImplicitPrelude)
1648
1649     , (Opt_GADTs,                  Opt_MonoLocalBinds)
1650     , (Opt_TypeFamilies,           Opt_MonoLocalBinds)
1651
1652     , (Opt_TypeFamilies,        Opt_KindSignatures)  -- Type families use kind signatures
1653                                                      -- all over the place
1654
1655     , (Opt_ImpredicativeTypes,  Opt_RankNTypes)
1656
1657         -- Record wild-cards implies field disambiguation
1658         -- Otherwise if you write (C {..}) you may well get
1659         -- stuff like " 'a' not in scope ", which is a bit silly
1660         -- if the compiler has just filled in field 'a' of constructor 'C'
1661     , (Opt_RecordWildCards,     Opt_DisambiguateRecordFields)
1662   ]
1663
1664 optLevelFlags :: [([Int], DynFlag)]
1665 optLevelFlags
1666   = [ ([0],     Opt_IgnoreInterfacePragmas)
1667     , ([0],     Opt_OmitInterfacePragmas)
1668
1669     , ([1,2],   Opt_IgnoreAsserts)
1670     , ([1,2],   Opt_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
1671                                          --              in PrelRules
1672     , ([1,2],   Opt_DoEtaReduction)
1673     , ([1,2],   Opt_CaseMerge)
1674     , ([1,2],   Opt_Strictness)
1675     , ([1,2],   Opt_CSE)
1676     , ([1,2],   Opt_FullLaziness)
1677     , ([1,2],   Opt_Specialise)
1678     , ([1,2],   Opt_FloatIn)
1679
1680     , ([2],     Opt_LiberateCase)
1681     , ([2],     Opt_SpecConstr)
1682     , ([2],     Opt_RegsGraph)
1683
1684 --     , ([2],     Opt_StaticArgumentTransformation)
1685 -- Max writes: I think it's probably best not to enable SAT with -O2 for the
1686 -- 6.10 release. The version of SAT in HEAD at the moment doesn't incorporate
1687 -- several improvements to the heuristics, and I'm concerned that without
1688 -- those changes SAT will interfere with some attempts to write "high
1689 -- performance Haskell", as we saw in some posts on Haskell-Cafe earlier
1690 -- this year. In particular, the version in HEAD lacks the tail call
1691 -- criterion, so many things that look like reasonable loops will be
1692 -- turned into functions with extra (unneccesary) thunk creation.
1693
1694     , ([0,1,2], Opt_DoLambdaEtaExpansion)
1695                 -- This one is important for a tiresome reason:
1696                 -- we want to make sure that the bindings for data
1697                 -- constructors are eta-expanded.  This is probably
1698                 -- a good thing anyway, but it seems fragile.
1699     ]
1700
1701 -- -----------------------------------------------------------------------------
1702 -- Standard sets of warning options
1703
1704 standardWarnings :: [DynFlag]
1705 standardWarnings
1706     = [ Opt_WarnWarningsDeprecations,
1707         Opt_WarnDeprecatedFlags,
1708         Opt_WarnUnrecognisedPragmas,
1709         Opt_WarnOverlappingPatterns,
1710         Opt_WarnMissingFields,
1711         Opt_WarnMissingMethods,
1712         Opt_WarnDuplicateExports,
1713         Opt_WarnLazyUnliftedBindings,
1714         Opt_WarnDodgyForeignImports,
1715         Opt_WarnWrongDoBind,
1716         Opt_WarnAlternativeLayoutRuleTransitional
1717       ]
1718
1719 minusWOpts :: [DynFlag]
1720 minusWOpts
1721     = standardWarnings ++
1722       [ Opt_WarnUnusedBinds,
1723         Opt_WarnUnusedMatches,
1724         Opt_WarnUnusedImports,
1725         Opt_WarnIncompletePatterns,
1726         Opt_WarnDodgyExports,
1727         Opt_WarnDodgyImports
1728       ]
1729
1730 minusWallOpts :: [DynFlag]
1731 minusWallOpts
1732     = minusWOpts ++
1733       [ Opt_WarnTypeDefaults,
1734         Opt_WarnNameShadowing,
1735         Opt_WarnMissingSigs,
1736         Opt_WarnHiShadows,
1737         Opt_WarnOrphans,
1738         Opt_WarnUnusedDoBind
1739       ]
1740
1741 -- minuswRemovesOpts should be every warning option
1742 minuswRemovesOpts :: [DynFlag]
1743 minuswRemovesOpts
1744     = minusWallOpts ++
1745       [Opt_WarnImplicitPrelude,
1746        Opt_WarnIncompletePatternsRecUpd,
1747        Opt_WarnMonomorphism,
1748        Opt_WarnUnrecognisedPragmas,
1749        Opt_WarnAutoOrphans,
1750        Opt_WarnTabs
1751       ]
1752
1753 enableGlasgowExts :: DynP ()
1754 enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
1755                        mapM_ setExtensionFlag glasgowExtsFlags
1756
1757 disableGlasgowExts :: DynP ()
1758 disableGlasgowExts = do unSetDynFlag Opt_PrintExplicitForalls
1759                         mapM_ unSetExtensionFlag glasgowExtsFlags
1760
1761 glasgowExtsFlags :: [ExtensionFlag]
1762 glasgowExtsFlags = [
1763              Opt_ForeignFunctionInterface
1764            , Opt_UnliftedFFITypes
1765            , Opt_ImplicitParams
1766            , Opt_ScopedTypeVariables
1767            , Opt_UnboxedTuples
1768            , Opt_TypeSynonymInstances
1769            , Opt_StandaloneDeriving
1770            , Opt_DeriveDataTypeable
1771            , Opt_DeriveFunctor
1772            , Opt_DeriveFoldable
1773            , Opt_DeriveTraversable
1774            , Opt_FlexibleContexts
1775            , Opt_FlexibleInstances
1776            , Opt_ConstrainedClassMethods
1777            , Opt_MultiParamTypeClasses
1778            , Opt_FunctionalDependencies
1779            , Opt_MagicHash
1780            , Opt_PolymorphicComponents
1781            , Opt_ExistentialQuantification
1782            , Opt_UnicodeSyntax
1783            , Opt_PostfixOperators
1784            , Opt_PatternGuards
1785            , Opt_LiberalTypeSynonyms
1786            , Opt_RankNTypes
1787            , Opt_TypeOperators
1788            , Opt_DoRec
1789            , Opt_ParallelListComp
1790            , Opt_EmptyDataDecls
1791            , Opt_KindSignatures
1792            , Opt_GeneralizedNewtypeDeriving ]
1793
1794 #ifdef GHCI
1795 -- Consult the RTS to find whether GHC itself has been built profiled
1796 -- If so, you can't use Template Haskell
1797 foreign import ccall unsafe "rts_isProfiled" rtsIsProfiledIO :: IO CInt
1798
1799 rtsIsProfiled :: Bool
1800 rtsIsProfiled = unsafePerformIO rtsIsProfiledIO /= 0
1801
1802 checkTemplateHaskellOk :: Bool -> DynP ()
1803 checkTemplateHaskellOk turn_on 
1804   | turn_on && rtsIsProfiled
1805   = addErr "You can't use Template Haskell with a profiled compiler"
1806   | otherwise
1807   = return ()
1808 #else
1809 -- In stage 1 we don't know that the RTS has rts_isProfiled, 
1810 -- so we simply say "ok".  It doesn't matter because TH isn't
1811 -- available in stage 1 anyway.
1812 checkTemplateHaskellOk turn_on = return ()
1813 #endif
1814
1815 {- **********************************************************************
1816 %*                                                                      *
1817                 DynFlags constructors
1818 %*                                                                      *
1819 %********************************************************************* -}
1820
1821 type DynP = EwM (CmdLineP DynFlags)
1822
1823 upd :: (DynFlags -> DynFlags) -> DynP ()
1824 upd f = liftEwM (do { dfs <- getCmdLineState
1825                     ; putCmdLineState $! (f dfs) })
1826
1827 --------------- Constructor functions for OptKind -----------------
1828 noArg :: (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1829 noArg fn = NoArg (upd fn)
1830
1831 noArgDF :: (DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
1832 noArgDF fn deprec = NoArg (upd fn >> deprecate deprec)
1833
1834 hasArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1835 hasArg fn = HasArg (upd . fn)
1836
1837 hasArgDF :: (String -> DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
1838 hasArgDF fn deprec = HasArg (\s -> do { upd (fn s)
1839                                       ; deprecate deprec })
1840
1841 intSuffix :: (Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
1842 intSuffix fn = IntSuffix (\n -> upd (fn n))
1843
1844 setDumpFlag :: DynFlag -> OptKind (CmdLineP DynFlags)
1845 setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag)
1846
1847 --------------------------
1848 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1849 setDynFlag   f = upd (\dfs -> dopt_set dfs f)
1850 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1851
1852 --------------------------
1853 setExtensionFlag, unSetExtensionFlag :: ExtensionFlag -> DynP ()
1854 setExtensionFlag f = do { upd (\dfs -> xopt_set dfs f)
1855                         ; mapM_ setExtensionFlag deps }
1856   where
1857     deps = [ d | (f', d) <- impliedFlags, f' == f ]
1858         -- When you set f, set the ones it implies
1859         -- NB: use setExtensionFlag recursively, in case the implied flags
1860         --     implies further flags
1861         -- When you un-set f, however, we don't un-set the things it implies
1862         --      (except for -fno-glasgow-exts, which is treated specially)
1863
1864 unSetExtensionFlag f = upd (\dfs -> xopt_unset dfs f)
1865
1866 --------------------------
1867 setDumpFlag' :: DynFlag -> DynP ()
1868 setDumpFlag' dump_flag
1869   = do { setDynFlag dump_flag
1870        ; when want_recomp forceRecompile }
1871   where
1872         -- Certain dumpy-things are really interested in what's going
1873         -- on during recompilation checking, so in those cases we
1874         -- don't want to turn it off.
1875     want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
1876                                        Opt_D_dump_hi_diffs]
1877
1878 forceRecompile :: DynP ()
1879 -- Whenver we -ddump, force recompilation (by switching off the 
1880 -- recompilation checker), else you don't see the dump! However, 
1881 -- don't switch it off in --make mode, else *everything* gets
1882 -- recompiled which probably isn't what you want
1883 forceRecompile = do { dfs <- liftEwM getCmdLineState
1884                     ; when (force_recomp dfs) (setDynFlag Opt_ForceRecomp) }
1885         where
1886           force_recomp dfs = isOneShot (ghcMode dfs)
1887
1888 setVerboseCore2Core :: DynP ()
1889 setVerboseCore2Core = do forceRecompile
1890                          setDynFlag Opt_D_verbose_core2core 
1891                          upd (\dfs -> dfs { shouldDumpSimplPhase = Nothing })
1892                          
1893
1894 setDumpSimplPhases :: String -> DynP ()
1895 setDumpSimplPhases s = do forceRecompile
1896                           upd (\dfs -> dfs { shouldDumpSimplPhase = Just spec })
1897   where
1898     spec = case s of { ('=' : s') -> s';  _ -> s }
1899
1900 setVerbosity :: Maybe Int -> DynP ()
1901 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1902
1903 addCmdlineHCInclude :: String -> DynP ()
1904 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1905
1906 extraPkgConf_ :: FilePath -> DynP ()
1907 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
1908
1909 exposePackage, exposePackageId, hidePackage, ignorePackage :: String -> DynP ()
1910 exposePackage p =
1911   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
1912 exposePackageId p =
1913   upd (\s -> s{ packageFlags = ExposePackageId p : packageFlags s })
1914 hidePackage p =
1915   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
1916 ignorePackage p =
1917   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
1918
1919 setPackageName :: String -> DynFlags -> DynFlags
1920 setPackageName p s =  s{ thisPackage = stringToPackageId p }
1921
1922 -- If we're linking a binary, then only targets that produce object
1923 -- code are allowed (requests for other target types are ignored).
1924 setTarget :: HscTarget -> DynP ()
1925 setTarget l = upd set
1926   where
1927    set dfs
1928      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
1929      | otherwise = dfs
1930
1931 -- Changes the target only if we're compiling object code.  This is
1932 -- used by -fasm and -fvia-C, which switch from one to the other, but
1933 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
1934 -- can be safely used in an OPTIONS_GHC pragma.
1935 setObjTarget :: HscTarget -> DynP ()
1936 setObjTarget l = upd set
1937   where
1938    set dfs
1939      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
1940      | otherwise = dfs
1941
1942 setOptLevel :: Int -> DynFlags -> DynFlags
1943 setOptLevel n dflags
1944    | hscTarget dflags == HscInterpreted && n > 0
1945         = dflags
1946             -- not in IO any more, oh well:
1947             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
1948    | otherwise
1949         = updOptLevel n dflags
1950
1951
1952 -- -Odph is equivalent to
1953 --
1954 --    -O2                               optimise as much as possible
1955 --    -fno-method-sharing               sharing specialisation defeats fusion
1956 --                                      sometimes
1957 --    -fdicts-cheap                     always inline dictionaries
1958 --    -fmax-simplifier-iterations20     this is necessary sometimes
1959 --    -fsimplifier-phases=3             we use an additional simplifier phase
1960 --                                      for fusion
1961 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
1962 --    -fno-spec-constr-count            SpecConstr as much as possible
1963 --    -finline-enough-args              hack to prevent excessive inlining
1964 --
1965 setDPHOpt :: DynFlags -> DynFlags
1966 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
1967                                          , simplPhases         = 3
1968                                          , specConstrThreshold = Nothing
1969                                          , specConstrCount     = Nothing
1970                                          })
1971                    `dopt_set`   Opt_DictsCheap
1972                    `dopt_unset` Opt_MethodSharing
1973
1974 data DPHBackend = DPHPar
1975                 | DPHSeq
1976                 | DPHThis
1977         deriving(Eq, Ord, Enum, Show)
1978
1979 setDPHBackend :: DPHBackend -> DynP ()
1980 setDPHBackend backend 
1981   = do
1982       upd $ \dflags -> dflags { dphBackend = backend }
1983       mapM_ exposePackage (dph_packages backend)
1984   where
1985     dph_packages DPHThis = []
1986     dph_packages DPHPar  = ["dph-prim-par", "dph-par"]
1987     dph_packages DPHSeq  = ["dph-prim-seq", "dph-seq"]
1988
1989 dphPackage :: DynFlags -> PackageId
1990 dphPackage dflags = case dphBackend dflags of
1991                       DPHPar  -> dphParPackageId
1992                       DPHSeq  -> dphSeqPackageId
1993                       DPHThis -> thisPackage dflags
1994
1995 setMainIs :: String -> DynP ()
1996 setMainIs arg
1997   | not (null main_fn) && isLower (head main_fn)
1998      -- The arg looked like "Foo.Bar.baz"
1999   = upd $ \d -> d{ mainFunIs = Just main_fn,
2000                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
2001
2002   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
2003   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
2004
2005   | otherwise                   -- The arg looked like "baz"
2006   = upd $ \d -> d{ mainFunIs = Just arg }
2007   where
2008     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
2009
2010 -----------------------------------------------------------------------------
2011 -- Paths & Libraries
2012
2013 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
2014
2015 -- -i on its own deletes the import paths
2016 addImportPath "" = upd (\s -> s{importPaths = []})
2017 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
2018
2019
2020 addLibraryPath p =
2021   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
2022
2023 addIncludePath p =
2024   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
2025
2026 addFrameworkPath p =
2027   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
2028
2029 #ifndef mingw32_TARGET_OS
2030 split_marker :: Char
2031 split_marker = ':'   -- not configurable (ToDo)
2032 #endif
2033
2034 splitPathList :: String -> [String]
2035 splitPathList s = filter notNull (splitUp s)
2036                 -- empty paths are ignored: there might be a trailing
2037                 -- ':' in the initial list, for example.  Empty paths can
2038                 -- cause confusion when they are translated into -I options
2039                 -- for passing to gcc.
2040   where
2041 #ifndef mingw32_TARGET_OS
2042     splitUp xs = split split_marker xs
2043 #else
2044      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
2045      --
2046      -- That is, if "foo:bar:baz" is used, this interpreted as
2047      -- consisting of three entries, 'foo', 'bar', 'baz'.
2048      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
2049      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
2050      --
2051      -- Notice that no attempt is made to fully replace the 'standard'
2052      -- split marker ':' with the Windows / DOS one, ';'. The reason being
2053      -- that this will cause too much breakage for users & ':' will
2054      -- work fine even with DOS paths, if you're not insisting on being silly.
2055      -- So, use either.
2056     splitUp []             = []
2057     splitUp (x:':':div:xs) | div `elem` dir_markers
2058                            = ((x:':':div:p): splitUp rs)
2059                            where
2060                               (p,rs) = findNextPath xs
2061           -- we used to check for existence of the path here, but that
2062           -- required the IO monad to be threaded through the command-line
2063           -- parser which is quite inconvenient.  The
2064     splitUp xs = cons p (splitUp rs)
2065                where
2066                  (p,rs) = findNextPath xs
2067
2068                  cons "" xs = xs
2069                  cons x  xs = x:xs
2070
2071     -- will be called either when we've consumed nought or the
2072     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
2073     -- finding the next split marker.
2074     findNextPath xs =
2075         case break (`elem` split_markers) xs of
2076            (p, _:ds) -> (p, ds)
2077            (p, xs)   -> (p, xs)
2078
2079     split_markers :: [Char]
2080     split_markers = [':', ';']
2081
2082     dir_markers :: [Char]
2083     dir_markers = ['/', '\\']
2084 #endif
2085
2086 -- -----------------------------------------------------------------------------
2087 -- tmpDir, where we store temporary files.
2088
2089 setTmpDir :: FilePath -> DynFlags -> DynFlags
2090 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
2091   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
2092   -- seem necessary now --SDM 7/2/2008
2093
2094 -----------------------------------------------------------------------------
2095 -- RTS opts
2096
2097 setRtsOpts :: String -> DynP ()
2098 setRtsOpts arg  = upd $ \ d -> d {rtsOpts = Just arg}
2099
2100 setRtsOptsEnabled :: RtsOptsEnabled -> DynP ()
2101 setRtsOptsEnabled arg  = upd $ \ d -> d {rtsOptsEnabled = arg}
2102
2103 -----------------------------------------------------------------------------
2104 -- Hpc stuff
2105
2106 setOptHpcDir :: String -> DynP ()
2107 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
2108
2109 -----------------------------------------------------------------------------
2110 -- Via-C compilation stuff
2111
2112 -- There are some options that we need to pass to gcc when compiling
2113 -- Haskell code via C, but are only supported by recent versions of
2114 -- gcc.  The configure script decides which of these options we need,
2115 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
2116 -- read before each via-C compilation.  The advantage of having these
2117 -- in a separate file is that the file can be created at install-time
2118 -- depending on the available gcc version, and even re-generated  later
2119 -- if gcc is upgraded.
2120 --
2121 -- The options below are not dependent on the version of gcc, only the
2122 -- platform.
2123
2124 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
2125                               [String]) -- for registerised HC compilations
2126 machdepCCOpts dflags = let (flagsAll, flagsRegHc) = machdepCCOpts' dflags
2127                        in (cCcOpts ++ flagsAll, flagsRegHc)
2128
2129 machdepCCOpts' :: DynFlags -> ([String], -- flags for all C compilations
2130                                [String]) -- for registerised HC compilations
2131 machdepCCOpts' _dflags
2132 #if alpha_TARGET_ARCH
2133         =       ( ["-w", "-mieee"
2134 #ifdef HAVE_THREADED_RTS_SUPPORT
2135                     , "-D_REENTRANT"
2136 #endif
2137                    ], [] )
2138         -- For now, to suppress the gcc warning "call-clobbered
2139         -- register used for global register variable", we simply
2140         -- disable all warnings altogether using the -w flag. Oh well.
2141
2142 #elif hppa_TARGET_ARCH
2143         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
2144         -- (very nice, but too bad the HP /usr/include files don't agree.)
2145         = ( ["-D_HPUX_SOURCE"], [] )
2146
2147 #elif m68k_TARGET_ARCH
2148       -- -fno-defer-pop : for the .hc files, we want all the pushing/
2149       --    popping of args to routines to be explicit; if we let things
2150       --    be deferred 'til after an STGJUMP, imminent death is certain!
2151       --
2152       -- -fomit-frame-pointer : *don't*
2153       --     It's better to have a6 completely tied up being a frame pointer
2154       --     rather than let GCC pick random things to do with it.
2155       --     (If we want to steal a6, then we would try to do things
2156       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
2157         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
2158
2159 #elif i386_TARGET_ARCH
2160       -- -fno-defer-pop : basically the same game as for m68k
2161       --
2162       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
2163       --   the fp (%ebp) for our register maps.
2164         =  let n_regs = stolen_x86_regs _dflags
2165            in
2166                     (
2167                       [ if opt_Static then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
2168                       ],
2169                       [ "-fno-defer-pop",
2170                         "-fomit-frame-pointer",
2171                         -- we want -fno-builtin, because when gcc inlines
2172                         -- built-in functions like memcpy() it tends to
2173                         -- run out of registers, requiring -monly-n-regs
2174                         "-fno-builtin",
2175                         "-DSTOLEN_X86_REGS="++show n_regs ]
2176                     )
2177
2178 #elif ia64_TARGET_ARCH
2179         = ( [], ["-fomit-frame-pointer", "-G0"] )
2180
2181 #elif x86_64_TARGET_ARCH
2182         = (
2183                 [],
2184                 ["-fomit-frame-pointer",
2185                  "-fno-asynchronous-unwind-tables",
2186                         -- the unwind tables are unnecessary for HC code,
2187                         -- and get in the way of -split-objs.  Another option
2188                         -- would be to throw them away in the mangler, but this
2189                         -- is easier.
2190                  "-fno-builtin"
2191                         -- calling builtins like strlen() using the FFI can
2192                         -- cause gcc to run out of regs, so use the external
2193                         -- version.
2194                 ] )
2195
2196 #elif sparc_TARGET_ARCH
2197         = ( [], ["-w"] )
2198         -- For now, to suppress the gcc warning "call-clobbered
2199         -- register used for global register variable", we simply
2200         -- disable all warnings altogether using the -w flag. Oh well.
2201
2202 #elif powerpc_apple_darwin_TARGET
2203       -- -no-cpp-precomp:
2204       --     Disable Apple's precompiling preprocessor. It's a great thing
2205       --     for "normal" programs, but it doesn't support register variable
2206       --     declarations.
2207         = ( [], ["-no-cpp-precomp"] )
2208 #else
2209         = ( [], [] )
2210 #endif
2211
2212 picCCOpts :: DynFlags -> [String]
2213 picCCOpts _dflags
2214 #if darwin_TARGET_OS
2215       -- Apple prefers to do things the other way round.
2216       -- PIC is on by default.
2217       -- -mdynamic-no-pic:
2218       --     Turn off PIC code generation.
2219       -- -fno-common:
2220       --     Don't generate "common" symbols - these are unwanted
2221       --     in dynamic libraries.
2222
2223     | opt_PIC
2224         = ["-fno-common", "-U __PIC__","-D__PIC__"]
2225     | otherwise
2226         = ["-mdynamic-no-pic"]
2227 #elif mingw32_TARGET_OS
2228       -- no -fPIC for Windows
2229     | opt_PIC
2230         = ["-U __PIC__","-D__PIC__"]
2231     | otherwise
2232         = []
2233 #else
2234       -- we need -fPIC for C files when we are compiling with -dynamic,
2235       -- otherwise things like stub.c files don't get compiled
2236       -- correctly.  They need to reference data in the Haskell
2237       -- objects, but can't without -fPIC.  See
2238       -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode
2239     | opt_PIC || not opt_Static
2240         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
2241     | otherwise
2242         = []
2243 #endif
2244
2245 -- -----------------------------------------------------------------------------
2246 -- Splitting
2247
2248 can_split :: Bool
2249 can_split = cSplitObjs == "YES"
2250
2251 -- -----------------------------------------------------------------------------
2252 -- Compiler Info
2253
2254 data Printable = String String
2255                | FromDynFlags (DynFlags -> String)
2256
2257 compilerInfo :: [(String, Printable)]
2258 compilerInfo = [("Project name",                String cProjectName),
2259                 ("Project version",             String cProjectVersion),
2260                 ("Booter version",              String cBooterVersion),
2261                 ("Stage",                       String cStage),
2262                 ("Build platform",              String cBuildPlatform),
2263                 ("Host platform",               String cHostPlatform),
2264                 ("Target platform",             String cTargetPlatform),
2265                 ("Have interpreter",            String cGhcWithInterpreter),
2266                 ("Object splitting",            String cSplitObjs),
2267                 ("Have native code generator",  String cGhcWithNativeCodeGen),
2268                 ("Have llvm code generator",    String cGhcWithLlvmCodeGen),
2269                 ("Use archives for ghci",       String (show cUseArchivesForGhci)),
2270                 ("Support SMP",                 String cGhcWithSMP),
2271                 ("Unregisterised",              String cGhcUnregisterised),
2272                 ("Tables next to code",         String cGhcEnableTablesNextToCode),
2273                 ("RTS ways",                    String cGhcRTSWays),
2274                 ("Leading underscore",          String cLeadingUnderscore),
2275                 ("Debug on",                    String (show debugIsOn)),
2276                 ("LibDir",                      FromDynFlags topDir),
2277                 ("Global Package DB",           FromDynFlags systemPackageConfig)
2278                ]
2279