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