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