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