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