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