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