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