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