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