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