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