First step for getting rid of the old -optdep flags
[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            ( panic, GhcException(..) )
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.Exception ( throwDyn )
82 import Control.Monad    ( when )
83
84 import Data.Char
85 import System.FilePath
86 import System.IO        ( stderr, hPutChar )
87
88 -- -----------------------------------------------------------------------------
89 -- DynFlags
90
91 data DynFlag
92
93    -- debugging flags
94    = Opt_D_dump_cmm
95    | Opt_D_dump_cmmz
96    | Opt_D_dump_cmmz_pretty
97    | Opt_D_dump_cps_cmm
98    | Opt_D_dump_cvt_cmm
99    | Opt_D_dump_asm
100    | Opt_D_dump_asm_native
101    | Opt_D_dump_asm_liveness
102    | Opt_D_dump_asm_coalesce
103    | Opt_D_dump_asm_regalloc
104    | Opt_D_dump_asm_regalloc_stages
105    | Opt_D_dump_asm_conflicts
106    | Opt_D_dump_asm_stats
107    | Opt_D_dump_cpranal
108    | Opt_D_dump_deriv
109    | Opt_D_dump_ds
110    | Opt_D_dump_flatC
111    | Opt_D_dump_foreign
112    | Opt_D_dump_inlinings
113    | Opt_D_dump_rule_firings
114    | Opt_D_dump_occur_anal
115    | Opt_D_dump_parsed
116    | Opt_D_dump_rn
117    | Opt_D_dump_simpl
118    | Opt_D_dump_simpl_iterations
119    | Opt_D_dump_simpl_phases
120    | Opt_D_dump_spec
121    | Opt_D_dump_prep
122    | Opt_D_dump_stg
123    | Opt_D_dump_stranal
124    | Opt_D_dump_tc
125    | Opt_D_dump_types
126    | Opt_D_dump_rules
127    | Opt_D_dump_cse
128    | Opt_D_dump_worker_wrapper
129    | Opt_D_dump_rn_trace
130    | Opt_D_dump_rn_stats
131    | Opt_D_dump_opt_cmm
132    | Opt_D_dump_simpl_stats
133    | Opt_D_dump_tc_trace
134    | Opt_D_dump_if_trace
135    | Opt_D_dump_splices
136    | Opt_D_dump_BCOs
137    | Opt_D_dump_vect
138    | Opt_D_dump_hpc
139    | Opt_D_source_stats
140    | Opt_D_verbose_core2core
141    | Opt_D_verbose_stg2stg
142    | Opt_D_dump_hi
143    | Opt_D_dump_hi_diffs
144    | Opt_D_dump_minimal_imports
145    | Opt_D_dump_mod_cycles
146    | Opt_D_dump_view_pattern_commoning
147    | Opt_D_faststring_stats
148    | Opt_DumpToFile                     -- ^ Append dump output to files instead of stdout.
149    | Opt_D_no_debug_output
150    | Opt_DoCoreLinting
151    | Opt_DoStgLinting
152    | Opt_DoCmmLinting
153    | Opt_DoAsmLinting
154
155    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
156    | Opt_WarnDuplicateExports
157    | Opt_WarnHiShadows
158    | Opt_WarnImplicitPrelude
159    | Opt_WarnIncompletePatterns
160    | Opt_WarnIncompletePatternsRecUpd
161    | Opt_WarnMissingFields
162    | Opt_WarnMissingMethods
163    | Opt_WarnMissingSigs
164    | Opt_WarnNameShadowing
165    | Opt_WarnOverlappingPatterns
166    | Opt_WarnSimplePatterns
167    | Opt_WarnTypeDefaults
168    | Opt_WarnMonomorphism
169    | Opt_WarnUnusedBinds
170    | Opt_WarnUnusedImports
171    | Opt_WarnUnusedMatches
172    | Opt_WarnWarningsDeprecations
173    | Opt_WarnDeprecatedFlags
174    | Opt_WarnDodgyImports
175    | Opt_WarnOrphans
176    | Opt_WarnTabs
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_WarnOverlappingPatterns,
797         Opt_WarnMissingFields,
798         Opt_WarnMissingMethods,
799         Opt_WarnDuplicateExports,
800         Opt_WarnDodgyForeignImports
801       ]
802
803 minusWOpts :: [DynFlag]
804 minusWOpts
805     = standardWarnings ++
806       [ Opt_WarnUnusedBinds,
807         Opt_WarnUnusedMatches,
808         Opt_WarnUnusedImports,
809         Opt_WarnIncompletePatterns,
810         Opt_WarnDodgyImports
811       ]
812
813 minusWallOpts :: [DynFlag]
814 minusWallOpts
815     = minusWOpts ++
816       [ Opt_WarnTypeDefaults,
817         Opt_WarnNameShadowing,
818         Opt_WarnMissingSigs,
819         Opt_WarnHiShadows,
820         Opt_WarnOrphans
821       ]
822
823 -- minuswRemovesOpts should be every warning option
824 minuswRemovesOpts :: [DynFlag]
825 minuswRemovesOpts
826     = minusWallOpts ++
827       [Opt_WarnImplicitPrelude,
828        Opt_WarnIncompletePatternsRecUpd,
829        Opt_WarnSimplePatterns,
830        Opt_WarnMonomorphism,
831        Opt_WarnTabs
832       ]
833
834 -- -----------------------------------------------------------------------------
835 -- CoreToDo:  abstraction of core-to-core passes to run.
836
837 data CoreToDo           -- These are diff core-to-core passes,
838                         -- which may be invoked in any order,
839                         -- as many times as you like.
840
841   = CoreDoSimplify      -- The core-to-core simplifier.
842         SimplifierMode
843         [SimplifierSwitch]
844                         -- Each run of the simplifier can take a different
845                         -- set of simplifier-specific flags.
846   | CoreDoFloatInwards
847   | CoreDoFloatOutwards FloatOutSwitches
848   | CoreLiberateCase
849   | CoreDoPrintCore
850   | CoreDoStaticArgs
851   | CoreDoStrictness
852   | CoreDoWorkerWrapper
853   | CoreDoSpecialising
854   | CoreDoSpecConstr
855   | CoreDoOldStrictness
856   | CoreDoGlomBinds
857   | CoreCSE
858   | CoreDoRuleCheck Int{-CompilerPhase-} String -- Check for non-application of rules
859                                                 -- matching this string
860   | CoreDoVectorisation DPHBackend
861   | CoreDoNothing                -- Useful when building up
862   | CoreDoPasses [CoreToDo]      -- lists of these things
863
864 data SimplifierMode             -- See comments in SimplMonad
865   = SimplGently
866   | SimplPhase Int [String]
867
868 data SimplifierSwitch
869   = MaxSimplifierIterations Int
870   | NoCaseOfCase
871
872 data FloatOutSwitches
873   = FloatOutSw  Bool    -- True <=> float lambdas to top level
874                 Bool    -- True <=> float constants to top level,
875                         --          even if they do not escape a lambda
876
877
878 -- The core-to-core pass ordering is derived from the DynFlags:
879 runWhen :: Bool -> CoreToDo -> CoreToDo
880 runWhen True  do_this = do_this
881 runWhen False _       = CoreDoNothing
882
883 runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo
884 runMaybe (Just x) f = f x
885 runMaybe Nothing  _ = CoreDoNothing
886
887 getCoreToDo :: DynFlags -> [CoreToDo]
888 getCoreToDo dflags
889   | Just todo <- coreToDo dflags = todo -- set explicitly by user
890   | otherwise = core_todo
891   where
892     opt_level     = optLevel dflags
893     phases        = simplPhases dflags
894     max_iter      = maxSimplIterations dflags
895     strictness    = dopt Opt_Strictness dflags
896     full_laziness = dopt Opt_FullLaziness dflags
897     cse           = dopt Opt_CSE dflags
898     spec_constr   = dopt Opt_SpecConstr dflags
899     liberate_case = dopt Opt_LiberateCase dflags
900     rule_check    = ruleCheck dflags
901     static_args   = dopt Opt_StaticArgumentTransformation dflags
902
903     maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase)
904
905     simpl_phase phase names iter
906       = CoreDoPasses
907           [ CoreDoSimplify (SimplPhase phase names) [
908               MaxSimplifierIterations iter
909             ],
910             maybe_rule_check phase
911           ]
912
913     vectorisation
914       = runWhen (dopt Opt_Vectorise dflags)
915         $ CoreDoPasses [ simpl_gently, CoreDoVectorisation (dphBackend dflags) ]
916
917
918                 -- By default, we have 2 phases before phase 0.
919
920                 -- Want to run with inline phase 2 after the specialiser to give
921                 -- maximum chance for fusion to work before we inline build/augment
922                 -- in phase 1.  This made a difference in 'ansi' where an
923                 -- overloaded function wasn't inlined till too late.
924
925                 -- Need phase 1 so that build/augment get
926                 -- inlined.  I found that spectral/hartel/genfft lost some useful
927                 -- strictness in the function sumcode' if augment is not inlined
928                 -- before strictness analysis runs
929     simpl_phases = CoreDoPasses [ simpl_phase phase ["main"] max_iter
930                                   | phase <- [phases, phases-1 .. 1] ]
931
932
933         -- initial simplify: mk specialiser happy: minimum effort please
934     simpl_gently = CoreDoSimplify SimplGently [
935                         --      Simplify "gently"
936                         -- Don't inline anything till full laziness has bitten
937                         -- In particular, inlining wrappers inhibits floating
938                         -- e.g. ...(case f x of ...)...
939                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
940                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
941                         -- and now the redex (f x) isn't floatable any more
942                         -- Similarly, don't apply any rules until after full
943                         -- laziness.  Notably, list fusion can prevent floating.
944
945             NoCaseOfCase,       -- Don't do case-of-case transformations.
946                                 -- This makes full laziness work better
947             MaxSimplifierIterations max_iter
948         ]
949
950     core_todo =
951      if opt_level == 0 then
952        [vectorisation,
953         simpl_phase 0 ["final"] max_iter]
954      else {- opt_level >= 1 -} [
955
956     -- We want to do the static argument transform before full laziness as it
957     -- may expose extra opportunities to float things outwards. However, to fix
958     -- up the output of the transformation we need at do at least one simplify
959     -- after this before anything else
960         runWhen static_args (CoreDoPasses [ simpl_gently, CoreDoStaticArgs ]),
961
962         -- We run vectorisation here for now, but we might also try to run
963         -- it later
964         vectorisation,
965
966         -- initial simplify: mk specialiser happy: minimum effort please
967         simpl_gently,
968
969         -- Specialisation is best done before full laziness
970         -- so that overloaded functions have all their dictionary lambdas manifest
971         CoreDoSpecialising,
972
973         runWhen full_laziness (CoreDoFloatOutwards (FloatOutSw False False)),
974
975         CoreDoFloatInwards,
976
977         simpl_phases,
978
979                 -- Phase 0: allow all Ids to be inlined now
980                 -- This gets foldr inlined before strictness analysis
981
982                 -- At least 3 iterations because otherwise we land up with
983                 -- huge dead expressions because of an infelicity in the
984                 -- simpifier.
985                 --      let k = BIG in foldr k z xs
986                 -- ==>  let k = BIG in letrec go = \xs -> ...(k x).... in go xs
987                 -- ==>  let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs
988                 -- Don't stop now!
989         simpl_phase 0 ["main"] (max max_iter 3),
990
991
992 #ifdef OLD_STRICTNESS
993         CoreDoOldStrictness,
994 #endif
995         runWhen strictness (CoreDoPasses [
996                 CoreDoStrictness,
997                 CoreDoWorkerWrapper,
998                 CoreDoGlomBinds,
999                 simpl_phase 0 ["post-worker-wrapper"] max_iter
1000                 ]),
1001
1002         runWhen full_laziness
1003           (CoreDoFloatOutwards (FloatOutSw False    -- Not lambdas
1004                                            True)),  -- Float constants
1005                 -- nofib/spectral/hartel/wang doubles in speed if you
1006                 -- do full laziness late in the day.  It only happens
1007                 -- after fusion and other stuff, so the early pass doesn't
1008                 -- catch it.  For the record, the redex is
1009                 --        f_el22 (f_el21 r_midblock)
1010
1011
1012         runWhen cse CoreCSE,
1013                 -- We want CSE to follow the final full-laziness pass, because it may
1014                 -- succeed in commoning up things floated out by full laziness.
1015                 -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
1016
1017         CoreDoFloatInwards,
1018
1019         maybe_rule_check 0,
1020
1021                 -- Case-liberation for -O2.  This should be after
1022                 -- strictness analysis and the simplification which follows it.
1023         runWhen liberate_case (CoreDoPasses [
1024             CoreLiberateCase,
1025             simpl_phase 0 ["post-liberate-case"] max_iter
1026             ]),         -- Run the simplifier after LiberateCase to vastly
1027                         -- reduce the possiblility of shadowing
1028                         -- Reason: see Note [Shadowing] in SpecConstr.lhs
1029
1030         runWhen spec_constr CoreDoSpecConstr,
1031
1032         maybe_rule_check 0,
1033
1034         -- Final clean-up simplification:
1035         simpl_phase 0 ["final"] max_iter
1036      ]
1037
1038 -- -----------------------------------------------------------------------------
1039 -- StgToDo:  abstraction of stg-to-stg passes to run.
1040
1041 data StgToDo
1042   = StgDoMassageForProfiling  -- should be (next to) last
1043   -- There's also setStgVarInfo, but its absolute "lastness"
1044   -- is so critical that it is hardwired in (no flag).
1045   | D_stg_stats
1046
1047 getStgToDo :: DynFlags -> [StgToDo]
1048 getStgToDo dflags
1049   | Just todo <- stgToDo dflags = todo -- set explicitly by user
1050   | otherwise = todo2
1051   where
1052         stg_stats = dopt Opt_StgStats dflags
1053
1054         todo1 = if stg_stats then [D_stg_stats] else []
1055
1056         todo2 | WayProf `elem` wayNames dflags
1057               = StgDoMassageForProfiling : todo1
1058               | otherwise
1059               = todo1
1060
1061 -- -----------------------------------------------------------------------------
1062 -- DynFlags parser
1063
1064 allFlags :: [String]
1065 allFlags = map ('-':) $
1066            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
1067            map ("fno-"++) flags ++
1068            map ("f"++) flags ++
1069            map ("X"++) supportedLanguages ++
1070            map ("XNo"++) supportedLanguages
1071     where ok (PrefixPred _ _) = False
1072           ok _ = True
1073           flags = [ name | (name, _, _) <- fFlags ]
1074
1075 dynamic_flags :: [Flag DynP]
1076 dynamic_flags = [
1077     Flag "n"              (NoArg  (setDynFlag Opt_DryRun)) Supported
1078   , Flag "cpp"            (NoArg  (setDynFlag Opt_Cpp)) Supported
1079   , Flag "F"              (NoArg  (setDynFlag Opt_Pp)) Supported
1080   , Flag "#include"       (HasArg (addCmdlineHCInclude)) Supported
1081   , Flag "v"              (OptIntSuffix setVerbosity) Supported
1082
1083         ------- Specific phases  --------------------------------------------
1084   , Flag "pgmL"           (HasArg (upd . setPgmL)) Supported
1085   , Flag "pgmP"           (HasArg (upd . setPgmP)) Supported
1086   , Flag "pgmF"           (HasArg (upd . setPgmF)) Supported
1087   , Flag "pgmc"           (HasArg (upd . setPgmc)) Supported
1088   , Flag "pgmm"           (HasArg (upd . setPgmm)) Supported
1089   , Flag "pgms"           (HasArg (upd . setPgms)) Supported
1090   , Flag "pgma"           (HasArg (upd . setPgma)) Supported
1091   , Flag "pgml"           (HasArg (upd . setPgml)) Supported
1092   , Flag "pgmdll"         (HasArg (upd . setPgmdll)) Supported
1093   , Flag "pgmwindres"     (HasArg (upd . setPgmwindres)) Supported
1094
1095   , Flag "optL"           (HasArg (upd . addOptL)) Supported
1096   , Flag "optP"           (HasArg (upd . addOptP)) Supported
1097   , Flag "optF"           (HasArg (upd . addOptF)) Supported
1098   , Flag "optc"           (HasArg (upd . addOptc)) Supported
1099   , Flag "optm"           (HasArg (upd . addOptm)) Supported
1100   , Flag "opta"           (HasArg (upd . addOpta)) Supported
1101   , Flag "optl"           (HasArg (upd . addOptl)) Supported
1102   , Flag "optwindres"     (HasArg (upd . addOptwindres)) Supported
1103
1104   , Flag "split-objs"
1105          (NoArg (if can_split then setDynFlag Opt_SplitObjs else return ()))
1106          Supported
1107
1108         -------- ghc -M -----------------------------------------------------
1109   , Flag "optdep-s"                 (HasArg (upd . addDepSuffix)) Supported
1110   , Flag "optdep-f"                 (HasArg (upd . setDepMakefile)) Supported
1111   , Flag "optdep-w"                 (NoArg  (upd (setDepWarnings False)))
1112          (Deprecated "-optdep-w doesn't do anything")
1113   , Flag "optdep--include-prelude"  (NoArg  (upd (setDepIncludePkgDeps True)))
1114          (Deprecated "Use -optdep--include-pkg-deps instead")
1115   , Flag "optdep--include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True))) Supported
1116   , Flag "optdep--exclude-module"   (HasArg (upd . addDepExcludeMod)) Supported
1117   , Flag "optdep-x"                 (HasArg (upd . addDepExcludeMod)) Supported
1118
1119         -------- Linking ----------------------------------------------------
1120   , Flag "c"              (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1121          Supported
1122   , Flag "no-link"        (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1123          (Deprecated "Use -c instead")
1124   , Flag "shared"         (NoArg (upd $ \d -> d{ ghcLink=LinkDynLib } ))
1125          Supported
1126   , Flag "dynload"        (HasArg (upd . parseDynLibLoaderMode))
1127          Supported
1128
1129         ------- Libraries ---------------------------------------------------
1130   , Flag "L"              (Prefix addLibraryPath ) Supported
1131   , Flag "l"              (AnySuffix (\s -> do upd (addOptl s))) Supported
1132
1133         ------- Frameworks --------------------------------------------------
1134         -- -framework-path should really be -F ...
1135   , Flag "framework-path" (HasArg addFrameworkPath ) Supported
1136   , Flag "framework"      (HasArg (upd . addCmdlineFramework)) Supported
1137
1138         ------- Output Redirection ------------------------------------------
1139   , Flag "odir"           (HasArg (upd . setObjectDir)) Supported
1140   , Flag "o"              (SepArg (upd . setOutputFile . Just)) Supported
1141   , Flag "ohi"            (HasArg (upd . setOutputHi   . Just )) Supported
1142   , Flag "osuf"           (HasArg (upd . setObjectSuf)) Supported
1143   , Flag "hcsuf"          (HasArg (upd . setHcSuf)) Supported
1144   , Flag "hisuf"          (HasArg (upd . setHiSuf)) Supported
1145   , Flag "hidir"          (HasArg (upd . setHiDir)) Supported
1146   , Flag "tmpdir"         (HasArg (upd . setTmpDir)) Supported
1147   , Flag "stubdir"        (HasArg (upd . setStubDir)) Supported
1148   , Flag "ddump-file-prefix" (HasArg (upd . setDumpPrefixForce . Just))
1149          Supported
1150
1151         ------- Keeping temporary files -------------------------------------
1152      -- These can be singular (think ghc -c) or plural (think ghc --make)
1153   , Flag "keep-hc-file"     (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1154   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles)) Supported
1155   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1156   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles)) Supported
1157   , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1158   , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported
1159      -- This only makes sense as plural
1160   , Flag "keep-tmp-files"   (NoArg (setDynFlag Opt_KeepTmpFiles)) Supported
1161
1162         ------- Miscellaneous ----------------------------------------------
1163   , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages)) Supported
1164   , Flag "no-hs-main"     (NoArg (setDynFlag Opt_NoHsMain)) Supported
1165   , Flag "main-is"        (SepArg setMainIs ) Supported
1166   , Flag "haddock"        (NoArg (setDynFlag Opt_Haddock)) Supported
1167   , Flag "haddock-opts"   (HasArg (upd . addHaddockOpts)) Supported
1168   , Flag "hpcdir"         (SepArg setOptHpcDir) Supported
1169
1170         ------- recompilation checker --------------------------------------
1171   , Flag "recomp"         (NoArg (unSetDynFlag Opt_ForceRecomp))
1172          (Deprecated "Use -fno-force-recomp instead")
1173   , Flag "no-recomp"      (NoArg (setDynFlag   Opt_ForceRecomp))
1174          (Deprecated "Use -fforce-recomp instead")
1175
1176         ------- Packages ----------------------------------------------------
1177   , Flag "package-conf"   (HasArg extraPkgConf_) Supported
1178   , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
1179          Supported
1180   , Flag "package-name"   (HasArg (upd . setPackageName)) Supported
1181   , Flag "package"        (HasArg exposePackage) Supported
1182   , Flag "hide-package"   (HasArg hidePackage) Supported
1183   , Flag "hide-all-packages" (NoArg (setDynFlag Opt_HideAllPackages))
1184          Supported
1185   , Flag "ignore-package" (HasArg ignorePackage)
1186          Supported
1187   , Flag "syslib"         (HasArg exposePackage)
1188          (Deprecated "Use -package instead")
1189
1190         ------ HsCpp opts ---------------------------------------------------
1191   , Flag "D"              (AnySuffix (upd . addOptP)) Supported
1192   , Flag "U"              (AnySuffix (upd . addOptP)) Supported
1193
1194         ------- Include/Import Paths ----------------------------------------
1195   , Flag "I"              (Prefix    addIncludePath) Supported
1196   , Flag "i"              (OptPrefix addImportPath ) Supported
1197
1198         ------ Debugging ----------------------------------------------------
1199   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats)) Supported
1200
1201   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
1202          Supported
1203   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
1204          Supported
1205   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
1206          Supported
1207   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
1208          Supported
1209   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
1210          Supported
1211   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
1212          Supported
1213   , Flag "ddump-asm-native"        (setDumpFlag Opt_D_dump_asm_native)
1214          Supported
1215   , Flag "ddump-asm-liveness"      (setDumpFlag Opt_D_dump_asm_liveness)
1216          Supported
1217   , Flag "ddump-asm-coalesce"      (setDumpFlag Opt_D_dump_asm_coalesce)
1218          Supported
1219   , Flag "ddump-asm-regalloc"      (setDumpFlag Opt_D_dump_asm_regalloc)
1220          Supported
1221   , Flag "ddump-asm-conflicts"     (setDumpFlag Opt_D_dump_asm_conflicts)
1222          Supported
1223   , Flag "ddump-asm-regalloc-stages"
1224                                  (setDumpFlag Opt_D_dump_asm_regalloc_stages)
1225          Supported
1226   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
1227          Supported
1228   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
1229          Supported
1230   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
1231          Supported
1232   , Flag "ddump-ds"                (setDumpFlag Opt_D_dump_ds)
1233          Supported
1234   , Flag "ddump-flatC"             (setDumpFlag Opt_D_dump_flatC)
1235          Supported
1236   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
1237          Supported
1238   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
1239          Supported
1240   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
1241          Supported
1242   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
1243          Supported
1244   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
1245          Supported
1246   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
1247          Supported
1248   , Flag "ddump-simpl"             (setDumpFlag Opt_D_dump_simpl)
1249          Supported
1250   , Flag "ddump-simpl-iterations"  (setDumpFlag Opt_D_dump_simpl_iterations)
1251          Supported
1252   , Flag "ddump-simpl-phases"      (OptPrefix setDumpSimplPhases)
1253          Supported
1254   , Flag "ddump-spec"              (setDumpFlag Opt_D_dump_spec)
1255          Supported
1256   , Flag "ddump-prep"              (setDumpFlag Opt_D_dump_prep)
1257          Supported
1258   , Flag "ddump-stg"               (setDumpFlag Opt_D_dump_stg)
1259          Supported
1260   , Flag "ddump-stranal"           (setDumpFlag Opt_D_dump_stranal)
1261          Supported
1262   , Flag "ddump-tc"                (setDumpFlag Opt_D_dump_tc)
1263          Supported
1264   , Flag "ddump-types"             (setDumpFlag Opt_D_dump_types)
1265          Supported
1266   , Flag "ddump-rules"             (setDumpFlag Opt_D_dump_rules)
1267          Supported
1268   , Flag "ddump-cse"               (setDumpFlag Opt_D_dump_cse)
1269          Supported
1270   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
1271          Supported
1272   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
1273          Supported
1274   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
1275          Supported
1276   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
1277          Supported
1278   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
1279          Supported
1280   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
1281          Supported
1282   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
1283          Supported
1284   , Flag "ddump-simpl-stats"       (setDumpFlag Opt_D_dump_simpl_stats)
1285          Supported
1286   , Flag "ddump-bcos"              (setDumpFlag Opt_D_dump_BCOs)
1287          Supported
1288   , Flag "dsource-stats"           (setDumpFlag Opt_D_source_stats)
1289          Supported
1290   , Flag "dverbose-core2core"      (NoArg setVerboseCore2Core)
1291          Supported
1292   , Flag "dverbose-stg2stg"        (setDumpFlag Opt_D_verbose_stg2stg)
1293          Supported
1294   , Flag "ddump-hi"                (setDumpFlag Opt_D_dump_hi)
1295          Supported
1296   , Flag "ddump-minimal-imports"   (setDumpFlag Opt_D_dump_minimal_imports)
1297          Supported
1298   , Flag "ddump-vect"              (setDumpFlag Opt_D_dump_vect)
1299          Supported
1300   , Flag "ddump-hpc"               (setDumpFlag Opt_D_dump_hpc)
1301          Supported
1302   , Flag "ddump-mod-cycles"        (setDumpFlag Opt_D_dump_mod_cycles)
1303          Supported
1304   , Flag "ddump-view-pattern-commoning" (setDumpFlag Opt_D_dump_view_pattern_commoning)
1305          Supported
1306   , Flag "ddump-to-file"           (setDumpFlag Opt_DumpToFile)
1307          Supported
1308   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
1309          Supported
1310
1311   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
1312          Supported
1313   , Flag "dstg-lint"               (NoArg (setDynFlag Opt_DoStgLinting))
1314          Supported
1315   , Flag "dcmm-lint"               (NoArg (setDynFlag Opt_DoCmmLinting))
1316          Supported
1317   , Flag "dasm-lint"               (NoArg (setDynFlag Opt_DoAsmLinting))
1318          Supported
1319   , Flag "dshow-passes"
1320          (NoArg (do setDynFlag Opt_ForceRecomp
1321                     setVerbosity (Just 2)))
1322          Supported
1323   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
1324          Supported
1325
1326         ------ Machine dependant (-m<blah>) stuff ---------------------------
1327
1328   , Flag "monly-2-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 2}) ))
1329          Supported
1330   , Flag "monly-3-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 3}) ))
1331          Supported
1332   , Flag "monly-4-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 4}) ))
1333          Supported
1334
1335      ------ Warning opts -------------------------------------------------
1336   , Flag "W"      (NoArg (mapM_ setDynFlag   minusWOpts))
1337          Supported
1338   , Flag "Werror" (NoArg (setDynFlag         Opt_WarnIsError))
1339          Supported
1340   , Flag "Wwarn"  (NoArg (unSetDynFlag       Opt_WarnIsError))
1341          Supported
1342   , Flag "Wall"   (NoArg (mapM_ setDynFlag   minusWallOpts))
1343          Supported
1344   , Flag "Wnot"   (NoArg (mapM_ unSetDynFlag minusWallOpts))
1345          (Deprecated "Use -w instead")
1346   , Flag "w"      (NoArg (mapM_ unSetDynFlag minuswRemovesOpts))
1347          Supported
1348
1349         ------ Optimisation flags ------------------------------------------
1350   , Flag "O"      (NoArg (upd (setOptLevel 1))) Supported
1351   , Flag "Onot"   (NoArg (upd (setOptLevel 0)))
1352          (Deprecated "Use -O0 instead")
1353   , Flag "Odph"   (NoArg (upd setDPHOpt)) Supported
1354   , Flag "O"      (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1355          Supported
1356                 -- If the number is missing, use 1
1357
1358   , Flag "fsimplifier-phases"
1359          (IntSuffix (\n -> upd (\dfs -> dfs{ simplPhases = n })))
1360          Supported
1361   , Flag "fmax-simplifier-iterations"
1362          (IntSuffix (\n -> upd (\dfs -> dfs{ maxSimplIterations = n })))
1363          Supported
1364
1365   , Flag "fspec-constr-threshold"
1366          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrThreshold = Just n })))
1367          Supported
1368   , Flag "fno-spec-constr-threshold"
1369          (NoArg (upd (\dfs -> dfs{ specConstrThreshold = Nothing })))
1370          Supported
1371   , Flag "fspec-constr-count"
1372          (IntSuffix (\n -> upd (\dfs -> dfs{ specConstrCount = Just n })))
1373          Supported
1374   , Flag "fno-spec-constr-count"
1375          (NoArg (upd (\dfs -> dfs{ specConstrCount = Nothing })))
1376          Supported
1377   , Flag "fliberate-case-threshold"
1378          (IntSuffix (\n -> upd (\dfs -> dfs{ liberateCaseThreshold = Just n })))
1379          Supported
1380   , Flag "fno-liberate-case-threshold"
1381          (NoArg (upd (\dfs -> dfs{ liberateCaseThreshold = Nothing })))
1382          Supported
1383
1384   , Flag "frule-check"
1385          (SepArg (\s -> upd (\dfs -> dfs{ ruleCheck = Just s })))
1386          Supported
1387   , Flag "fcontext-stack"
1388          (IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
1389          Supported
1390
1391         ------ DPH flags ----------------------------------------------------
1392
1393   , Flag "fdph-seq"
1394          (NoArg (upd (setDPHBackend DPHSeq)))
1395          Supported
1396   , Flag "fdph-par"
1397          (NoArg (upd (setDPHBackend DPHPar)))
1398          Supported
1399
1400         ------ Compiler flags -----------------------------------------------
1401
1402   , Flag "fasm"             (NoArg (setObjTarget HscAsm)) Supported
1403   , Flag "fvia-c"           (NoArg (setObjTarget HscC)) Supported
1404   , Flag "fvia-C"           (NoArg (setObjTarget HscC)) Supported
1405
1406   , Flag "fno-code"         (NoArg (setTarget HscNothing)) Supported
1407   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted)) Supported
1408   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget)) Supported
1409
1410   , Flag "fglasgow-exts"    (NoArg (mapM_ setDynFlag   glasgowExtsFlags))
1411          Supported
1412   , Flag "fno-glasgow-exts" (NoArg (mapM_ unSetDynFlag glasgowExtsFlags))
1413          Supported
1414  ]
1415  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
1416  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
1417  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
1418  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
1419
1420 mkFlag :: Bool -- True => turn it on, False => turn it off
1421        -> String
1422        -> (DynFlag -> DynP ())
1423        -> (String, DynFlag, Bool -> Deprecated)
1424        -> Flag DynP
1425 mkFlag turnOn flagPrefix f (name, dynflag, deprecated)
1426     = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
1427
1428 deprecatedForLanguage :: String -> Bool -> Deprecated
1429 deprecatedForLanguage lang turnOn =
1430     Deprecated ("Use the " ++ prefix ++ lang ++ " language instead")
1431     where prefix = if turnOn then "" else "No"
1432
1433 -- these -f<blah> flags can all be reversed with -fno-<blah>
1434
1435 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
1436 fFlags = [
1437   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
1438   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, const Supported ),
1439   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, const Supported ),
1440   ( "warn-hi-shadowing",                Opt_WarnHiShadows, const Supported ),
1441   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, const Supported ),
1442   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, const Supported ),
1443   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, const Supported ),
1444   ( "warn-missing-fields",              Opt_WarnMissingFields, const Supported ),
1445   ( "warn-missing-methods",             Opt_WarnMissingMethods, const Supported ),
1446   ( "warn-missing-signatures",          Opt_WarnMissingSigs, const Supported ),
1447   ( "warn-name-shadowing",              Opt_WarnNameShadowing, const Supported ),
1448   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns, const Supported ),
1449   ( "warn-simple-patterns",             Opt_WarnSimplePatterns, const Supported ),
1450   ( "warn-type-defaults",               Opt_WarnTypeDefaults, const Supported ),
1451   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism, const Supported ),
1452   ( "warn-unused-binds",                Opt_WarnUnusedBinds, const Supported ),
1453   ( "warn-unused-imports",              Opt_WarnUnusedImports, const Supported ),
1454   ( "warn-unused-matches",              Opt_WarnUnusedMatches, const Supported ),
1455   ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, const Supported ),
1456   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, const Supported ),
1457   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
1458   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
1459   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
1460   ( "strictness",                       Opt_Strictness, const Supported ),
1461   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
1462   ( "full-laziness",                    Opt_FullLaziness, const Supported ),
1463   ( "liberate-case",                    Opt_LiberateCase, const Supported ),
1464   ( "spec-constr",                      Opt_SpecConstr, const Supported ),
1465   ( "cse",                              Opt_CSE, const Supported ),
1466   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas, const Supported ),
1467   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas, const Supported ),
1468   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion, const Supported ),
1469   ( "ignore-asserts",                   Opt_IgnoreAsserts, const Supported ),
1470   ( "do-eta-reduction",                 Opt_DoEtaReduction, const Supported ),
1471   ( "case-merge",                       Opt_CaseMerge, const Supported ),
1472   ( "unbox-strict-fields",              Opt_UnboxStrictFields, const Supported ),
1473   ( "method-sharing",                   Opt_MethodSharing, const Supported ),
1474   ( "dicts-cheap",                      Opt_DictsCheap, const Supported ),
1475   ( "excess-precision",                 Opt_ExcessPrecision, const Supported ),
1476   ( "asm-mangling",                     Opt_DoAsmMangling, const Supported ),
1477   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
1478   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
1479   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
1480   ( "rewrite-rules",                    Opt_RewriteRules, const Supported ),
1481   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
1482   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
1483   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
1484   ( "print-bind-contents",              Opt_PrintBindContents, const Supported ),
1485   ( "run-cps",                          Opt_RunCPSZ, const Supported ),
1486   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, const Supported ),
1487   ( "vectorise",                        Opt_Vectorise, const Supported ),
1488   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
1489   ( "regs-iterative",                   Opt_RegsIterative, const Supported ),
1490   ( "th",                               Opt_TemplateHaskell,
1491     deprecatedForLanguage "TemplateHaskell" ),
1492   ( "fi",                               Opt_ForeignFunctionInterface,
1493     deprecatedForLanguage "ForeignFunctionInterface" ),
1494   ( "ffi",                              Opt_ForeignFunctionInterface,
1495     deprecatedForLanguage "ForeignFunctionInterface" ),
1496   ( "arrows",                           Opt_Arrows,
1497     deprecatedForLanguage "Arrows" ),
1498   ( "generics",                         Opt_Generics,
1499     deprecatedForLanguage "Generics" ),
1500   ( "implicit-prelude",                 Opt_ImplicitPrelude,
1501     deprecatedForLanguage "ImplicitPrelude" ),
1502   ( "bang-patterns",                    Opt_BangPatterns,
1503     deprecatedForLanguage "BangPatterns" ),
1504   ( "monomorphism-restriction",         Opt_MonomorphismRestriction,
1505     deprecatedForLanguage "MonomorphismRestriction" ),
1506   ( "mono-pat-binds",                   Opt_MonoPatBinds,
1507     deprecatedForLanguage "MonoPatBinds" ),
1508   ( "extended-default-rules",           Opt_ExtendedDefaultRules,
1509     deprecatedForLanguage "ExtendedDefaultRules" ),
1510   ( "implicit-params",                  Opt_ImplicitParams,
1511     deprecatedForLanguage "ImplicitParams" ),
1512   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
1513     deprecatedForLanguage "ScopedTypeVariables" ),
1514   ( "parr",                             Opt_PArr,
1515     deprecatedForLanguage "PArr" ),
1516   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
1517     deprecatedForLanguage "OverlappingInstances" ),
1518   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
1519     deprecatedForLanguage "UndecidableInstances" ),
1520   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
1521     deprecatedForLanguage "IncoherentInstances" ),
1522   ( "gen-manifest",                     Opt_GenManifest, const Supported ),
1523   ( "embed-manifest",                   Opt_EmbedManifest, const Supported )
1524   ]
1525
1526 supportedLanguages :: [String]
1527 supportedLanguages = [ name | (name, _, _) <- xFlags ]
1528
1529 -- This may contain duplicates
1530 languageOptions :: [DynFlag]
1531 languageOptions = [ dynFlag | (_, dynFlag, _) <- xFlags ]
1532
1533 -- These -X<blah> flags can all be reversed with -XNo<blah>
1534 xFlags :: [(String, DynFlag, Bool -> Deprecated)]
1535 xFlags = [
1536   ( "CPP",                              Opt_Cpp, const Supported ),
1537   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
1538   ( "PatternGuards",                    Opt_PatternGuards, const Supported ),
1539   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, const Supported ),
1540   ( "MagicHash",                        Opt_MagicHash, const Supported ),
1541   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
1542   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
1543   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
1544   ( "PatternSignatures",                Opt_PatternSignatures, const Supported ),
1545   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
1546   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
1547   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
1548   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, const Supported ),
1549   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, const Supported ),
1550   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, const Supported ),
1551   ( "Rank2Types",                       Opt_Rank2Types, const Supported ),
1552   ( "RankNTypes",                       Opt_RankNTypes, const Supported ),
1553   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, const Supported ),
1554   ( "TypeOperators",                    Opt_TypeOperators, const Supported ),
1555   ( "RecursiveDo",                      Opt_RecursiveDo, const Supported ),
1556   ( "Arrows",                           Opt_Arrows, const Supported ),
1557   ( "PArr",                             Opt_PArr, const Supported ),
1558   ( "TemplateHaskell",                  Opt_TemplateHaskell, const Supported ),
1559   ( "QuasiQuotes",                      Opt_QuasiQuotes, const Supported ),
1560   ( "Generics",                         Opt_Generics, const Supported ),
1561   -- On by default:
1562   ( "ImplicitPrelude",                  Opt_ImplicitPrelude, const Supported ),
1563   ( "RecordWildCards",                  Opt_RecordWildCards, const Supported ),
1564   ( "NamedFieldPuns",                   Opt_RecordPuns, const Supported ),
1565   ( "RecordPuns",                       Opt_RecordPuns,
1566     deprecatedForLanguage "NamedFieldPuns" ),
1567   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, const Supported ),
1568   ( "OverloadedStrings",                Opt_OverloadedStrings, const Supported ),
1569   ( "GADTs",                            Opt_GADTs, const Supported ),
1570   ( "ViewPatterns",                     Opt_ViewPatterns, const Supported ),
1571   ( "TypeFamilies",                     Opt_TypeFamilies, const Supported ),
1572   ( "BangPatterns",                     Opt_BangPatterns, const Supported ),
1573   -- On by default:
1574   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, const Supported ),
1575   -- On by default (which is not strictly H98):
1576   ( "MonoPatBinds",                     Opt_MonoPatBinds, const Supported ),
1577   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
1578   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
1579   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
1580   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
1581   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
1582   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
1583   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
1584   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, const Supported ),
1585   ( "FlexibleContexts",                 Opt_FlexibleContexts, const Supported ),
1586   ( "FlexibleInstances",                Opt_FlexibleInstances, const Supported ),
1587   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods, const Supported ),
1588   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses, const Supported ),
1589   ( "FunctionalDependencies",           Opt_FunctionalDependencies, const Supported ),
1590   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, const Supported ),
1591   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
1592   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
1593   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported )
1594   ]
1595
1596 impliedFlags :: [(DynFlag, [DynFlag])]
1597 impliedFlags = [
1598    ( Opt_GADTs,               [Opt_RelaxedPolyRec] )    -- We want type-sig variables to
1599                                                         --      be completely rigid for GADTs
1600  , ( Opt_ScopedTypeVariables, [Opt_RelaxedPolyRec] )    -- Ditto for scoped type variables; see
1601                                                         --      Note [Scoped tyvars] in TcBinds
1602   ]
1603
1604 glasgowExtsFlags :: [DynFlag]
1605 glasgowExtsFlags = [
1606              Opt_PrintExplicitForalls
1607            , Opt_ForeignFunctionInterface
1608            , Opt_UnliftedFFITypes
1609            , Opt_GADTs
1610            , Opt_ImplicitParams
1611            , Opt_ScopedTypeVariables
1612            , Opt_UnboxedTuples
1613            , Opt_TypeSynonymInstances
1614            , Opt_StandaloneDeriving
1615            , Opt_DeriveDataTypeable
1616            , Opt_FlexibleContexts
1617            , Opt_FlexibleInstances
1618            , Opt_ConstrainedClassMethods
1619            , Opt_MultiParamTypeClasses
1620            , Opt_FunctionalDependencies
1621            , Opt_MagicHash
1622            , Opt_PolymorphicComponents
1623            , Opt_ExistentialQuantification
1624            , Opt_UnicodeSyntax
1625            , Opt_PostfixOperators
1626            , Opt_PatternGuards
1627            , Opt_LiberalTypeSynonyms
1628            , Opt_RankNTypes
1629            , Opt_ImpredicativeTypes
1630            , Opt_TypeOperators
1631            , Opt_RecursiveDo
1632            , Opt_ParallelListComp
1633            , Opt_EmptyDataDecls
1634            , Opt_KindSignatures
1635            , Opt_PatternSignatures
1636            , Opt_GeneralizedNewtypeDeriving
1637            , Opt_TypeFamilies ]
1638
1639 -- -----------------------------------------------------------------------------
1640 -- Parsing the dynamic flags.
1641
1642 parseDynamicFlags :: DynFlags -> [String] -> IO (DynFlags, [String], [String])
1643 parseDynamicFlags dflags args = do
1644   -- XXX Legacy support code
1645   -- We used to accept things like
1646   --     optdep-f  -optdepdepend
1647   --     optdep-f  -optdep depend
1648   --     optdep -f -optdepdepend
1649   --     optdep -f -optdep depend
1650   -- but the spaces trip up proper argument handling. So get rid of them.
1651   let f ("-optdep" : x : xs) = ("-optdep" ++ x) : f xs
1652       f (x : xs) = x : f xs
1653       f xs = xs
1654       args' = f args
1655   let ((leftover, errs, warns), dflags')
1656           = runCmdLine (processArgs dynamic_flags args') dflags
1657   when (not (null errs)) $ do
1658     throwDyn (UsageError (unlines errs))
1659   return (dflags', leftover, warns)
1660
1661 type DynP = CmdLineP DynFlags
1662
1663 upd :: (DynFlags -> DynFlags) -> DynP ()
1664 upd f = do
1665    dfs <- getCmdLineState
1666    putCmdLineState $! (f dfs)
1667
1668 --------------------------
1669 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1670 setDynFlag f = upd (\dfs -> foldl dopt_set (dopt_set dfs f) deps)
1671   where
1672     deps = [ d | (f', ds) <- impliedFlags, f' == f, d <- ds ]
1673         -- When you set f, set the ones it implies
1674         -- When you un-set f, however, we don't un-set the things it implies
1675         --      (except for -fno-glasgow-exts, which is treated specially)
1676
1677 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1678
1679 --------------------------
1680 setDumpFlag :: DynFlag -> OptKind DynP
1681 setDumpFlag dump_flag
1682   | force_recomp   = NoArg (setDynFlag Opt_ForceRecomp >> setDynFlag dump_flag)
1683   | otherwise      = NoArg (setDynFlag dump_flag)
1684   where
1685         -- Whenver we -ddump, switch off the recompilation checker,
1686         -- else you don't see the dump!
1687         -- However, certain dumpy-things are really interested in what's going
1688         -- on during recompilation checking, so in those cases we
1689         -- don't want to turn it off.
1690    force_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
1691                                        Opt_D_dump_hi_diffs]
1692
1693 setVerboseCore2Core :: DynP ()
1694 setVerboseCore2Core = do setDynFlag Opt_ForceRecomp
1695                          setDynFlag Opt_D_verbose_core2core
1696                          upd (\s -> s { shouldDumpSimplPhase = const True })
1697
1698 setDumpSimplPhases :: String -> DynP ()
1699 setDumpSimplPhases s = do setDynFlag Opt_ForceRecomp
1700                           upd (\s -> s { shouldDumpSimplPhase = spec })
1701   where
1702     spec :: SimplifierMode -> Bool
1703     spec = join (||)
1704          . map (join (&&) . map match . split ':')
1705          . split ','
1706          $ case s of
1707              '=' : s' -> s'
1708              _        -> s
1709
1710     join :: (Bool -> Bool -> Bool)
1711          -> [SimplifierMode -> Bool]
1712          -> SimplifierMode -> Bool
1713     join _  [] = const True
1714     join op ss = foldr1 (\f g x -> f x `op` g x) ss
1715
1716     match :: String -> SimplifierMode -> Bool
1717     match "" = const True
1718     match s  = case reads s of
1719                 [(n,"")] -> phase_num  n
1720                 _        -> phase_name s
1721
1722     phase_num :: Int -> SimplifierMode -> Bool
1723     phase_num n (SimplPhase k _) = n == k
1724     phase_num _ _                = False
1725
1726     phase_name :: String -> SimplifierMode -> Bool
1727     phase_name s SimplGently       = s == "gentle"
1728     phase_name s (SimplPhase _ ss) = s `elem` ss
1729
1730 setVerbosity :: Maybe Int -> DynP ()
1731 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1732
1733 addCmdlineHCInclude :: String -> DynP ()
1734 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1735
1736 extraPkgConf_ :: FilePath -> DynP ()
1737 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
1738
1739 exposePackage, hidePackage, ignorePackage :: String -> DynP ()
1740 exposePackage p =
1741   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
1742 hidePackage p =
1743   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
1744 ignorePackage p =
1745   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
1746
1747 setPackageName :: String -> DynFlags -> DynFlags
1748 setPackageName p
1749   | Nothing <- unpackPackageId pid
1750   = throwDyn (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
1751   | otherwise
1752   = \s -> s{ thisPackage = pid }
1753   where
1754         pid = stringToPackageId p
1755
1756 -- If we're linking a binary, then only targets that produce object
1757 -- code are allowed (requests for other target types are ignored).
1758 setTarget :: HscTarget -> DynP ()
1759 setTarget l = upd set
1760   where
1761    set dfs
1762      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
1763      | otherwise = dfs
1764
1765 -- Changes the target only if we're compiling object code.  This is
1766 -- used by -fasm and -fvia-C, which switch from one to the other, but
1767 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
1768 -- can be safely used in an OPTIONS_GHC pragma.
1769 setObjTarget :: HscTarget -> DynP ()
1770 setObjTarget l = upd set
1771   where
1772    set dfs
1773      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
1774      | otherwise = dfs
1775
1776 setOptLevel :: Int -> DynFlags -> DynFlags
1777 setOptLevel n dflags
1778    | hscTarget dflags == HscInterpreted && n > 0
1779         = dflags
1780             -- not in IO any more, oh well:
1781             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
1782    | otherwise
1783         = updOptLevel n dflags
1784
1785
1786 -- -Odph is equivalent to
1787 --
1788 --    -O2                               optimise as much as possible
1789 --    -fno-method-sharing               sharing specialisation defeats fusion
1790 --                                      sometimes
1791 --    -fdicts-cheap                     always inline dictionaries
1792 --    -fmax-simplifier-iterations20     this is necessary sometimes
1793 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
1794 --
1795 setDPHOpt :: DynFlags -> DynFlags
1796 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
1797                                          , specConstrThreshold = Nothing
1798                                          })
1799                    `dopt_set`   Opt_DictsCheap
1800                    `dopt_unset` Opt_MethodSharing
1801
1802 data DPHBackend = DPHPar
1803                 | DPHSeq
1804
1805 setDPHBackend :: DPHBackend -> DynFlags -> DynFlags
1806 setDPHBackend backend dflags = dflags { dphBackend = backend }
1807
1808
1809 setMainIs :: String -> DynP ()
1810 setMainIs arg
1811   | not (null main_fn) && isLower (head main_fn)
1812      -- The arg looked like "Foo.Bar.baz"
1813   = upd $ \d -> d{ mainFunIs = Just main_fn,
1814                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
1815
1816   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
1817   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
1818
1819   | otherwise                   -- The arg looked like "baz"
1820   = upd $ \d -> d{ mainFunIs = Just arg }
1821   where
1822     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
1823
1824 -----------------------------------------------------------------------------
1825 -- Paths & Libraries
1826
1827 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
1828
1829 -- -i on its own deletes the import paths
1830 addImportPath "" = upd (\s -> s{importPaths = []})
1831 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
1832
1833
1834 addLibraryPath p =
1835   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
1836
1837 addIncludePath p =
1838   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
1839
1840 addFrameworkPath p =
1841   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
1842
1843 #ifndef mingw32_TARGET_OS
1844 split_marker :: Char
1845 split_marker = ':'   -- not configurable (ToDo)
1846 #endif
1847
1848 splitPathList :: String -> [String]
1849 splitPathList s = filter notNull (splitUp s)
1850                 -- empty paths are ignored: there might be a trailing
1851                 -- ':' in the initial list, for example.  Empty paths can
1852                 -- cause confusion when they are translated into -I options
1853                 -- for passing to gcc.
1854   where
1855 #ifndef mingw32_TARGET_OS
1856     splitUp xs = split split_marker xs
1857 #else
1858      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
1859      --
1860      -- That is, if "foo:bar:baz" is used, this interpreted as
1861      -- consisting of three entries, 'foo', 'bar', 'baz'.
1862      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
1863      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
1864      --
1865      -- Notice that no attempt is made to fully replace the 'standard'
1866      -- split marker ':' with the Windows / DOS one, ';'. The reason being
1867      -- that this will cause too much breakage for users & ':' will
1868      -- work fine even with DOS paths, if you're not insisting on being silly.
1869      -- So, use either.
1870     splitUp []             = []
1871     splitUp (x:':':div:xs) | div `elem` dir_markers
1872                            = ((x:':':div:p): splitUp rs)
1873                            where
1874                               (p,rs) = findNextPath xs
1875           -- we used to check for existence of the path here, but that
1876           -- required the IO monad to be threaded through the command-line
1877           -- parser which is quite inconvenient.  The
1878     splitUp xs = cons p (splitUp rs)
1879                where
1880                  (p,rs) = findNextPath xs
1881
1882                  cons "" xs = xs
1883                  cons x  xs = x:xs
1884
1885     -- will be called either when we've consumed nought or the
1886     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
1887     -- finding the next split marker.
1888     findNextPath xs =
1889         case break (`elem` split_markers) xs of
1890            (p, _:ds) -> (p, ds)
1891            (p, xs)   -> (p, xs)
1892
1893     split_markers :: [Char]
1894     split_markers = [':', ';']
1895
1896     dir_markers :: [Char]
1897     dir_markers = ['/', '\\']
1898 #endif
1899
1900 -- -----------------------------------------------------------------------------
1901 -- tmpDir, where we store temporary files.
1902
1903 setTmpDir :: FilePath -> DynFlags -> DynFlags
1904 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
1905   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
1906   -- seem necessary now --SDM 7/2/2008
1907
1908 -----------------------------------------------------------------------------
1909 -- Hpc stuff
1910
1911 setOptHpcDir :: String -> DynP ()
1912 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
1913
1914 -----------------------------------------------------------------------------
1915 -- Via-C compilation stuff
1916
1917 -- There are some options that we need to pass to gcc when compiling
1918 -- Haskell code via C, but are only supported by recent versions of
1919 -- gcc.  The configure script decides which of these options we need,
1920 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
1921 -- read before each via-C compilation.  The advantage of having these
1922 -- in a separate file is that the file can be created at install-time
1923 -- depending on the available gcc version, and even re-generated  later
1924 -- if gcc is upgraded.
1925 --
1926 -- The options below are not dependent on the version of gcc, only the
1927 -- platform.
1928
1929 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
1930                               [String]) -- for registerised HC compilations
1931 machdepCCOpts _dflags
1932 #if alpha_TARGET_ARCH
1933         =       ( ["-w", "-mieee"
1934 #ifdef HAVE_THREADED_RTS_SUPPORT
1935                     , "-D_REENTRANT"
1936 #endif
1937                    ], [] )
1938         -- For now, to suppress the gcc warning "call-clobbered
1939         -- register used for global register variable", we simply
1940         -- disable all warnings altogether using the -w flag. Oh well.
1941
1942 #elif hppa_TARGET_ARCH
1943         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
1944         -- (very nice, but too bad the HP /usr/include files don't agree.)
1945         = ( ["-D_HPUX_SOURCE"], [] )
1946
1947 #elif m68k_TARGET_ARCH
1948       -- -fno-defer-pop : for the .hc files, we want all the pushing/
1949       --    popping of args to routines to be explicit; if we let things
1950       --    be deferred 'til after an STGJUMP, imminent death is certain!
1951       --
1952       -- -fomit-frame-pointer : *don't*
1953       --     It's better to have a6 completely tied up being a frame pointer
1954       --     rather than let GCC pick random things to do with it.
1955       --     (If we want to steal a6, then we would try to do things
1956       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
1957         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
1958
1959 #elif i386_TARGET_ARCH
1960       -- -fno-defer-pop : basically the same game as for m68k
1961       --
1962       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
1963       --   the fp (%ebp) for our register maps.
1964         =  let n_regs = stolen_x86_regs _dflags
1965                sta = opt_Static
1966            in
1967                     ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
1968                       ],
1969                       [ "-fno-defer-pop",
1970                         "-fomit-frame-pointer",
1971                         -- we want -fno-builtin, because when gcc inlines
1972                         -- built-in functions like memcpy() it tends to
1973                         -- run out of registers, requiring -monly-n-regs
1974                         "-fno-builtin",
1975                         "-DSTOLEN_X86_REGS="++show n_regs ]
1976                     )
1977
1978 #elif ia64_TARGET_ARCH
1979         = ( [], ["-fomit-frame-pointer", "-G0"] )
1980
1981 #elif x86_64_TARGET_ARCH
1982         = ( [], ["-fomit-frame-pointer",
1983                  "-fno-asynchronous-unwind-tables",
1984                         -- the unwind tables are unnecessary for HC code,
1985                         -- and get in the way of -split-objs.  Another option
1986                         -- would be to throw them away in the mangler, but this
1987                         -- is easier.
1988                  "-fno-builtin"
1989                         -- calling builtins like strlen() using the FFI can
1990                         -- cause gcc to run out of regs, so use the external
1991                         -- version.
1992                 ] )
1993
1994 #elif sparc_TARGET_ARCH
1995         = ( [], ["-w"] )
1996         -- For now, to suppress the gcc warning "call-clobbered
1997         -- register used for global register variable", we simply
1998         -- disable all warnings altogether using the -w flag. Oh well.
1999
2000 #elif powerpc_apple_darwin_TARGET
2001       -- -no-cpp-precomp:
2002       --     Disable Apple's precompiling preprocessor. It's a great thing
2003       --     for "normal" programs, but it doesn't support register variable
2004       --     declarations.
2005         = ( [], ["-no-cpp-precomp"] )
2006 #else
2007         = ( [], [] )
2008 #endif
2009
2010 picCCOpts :: DynFlags -> [String]
2011 picCCOpts _dflags
2012 #if darwin_TARGET_OS
2013       -- Apple prefers to do things the other way round.
2014       -- PIC is on by default.
2015       -- -mdynamic-no-pic:
2016       --     Turn off PIC code generation.
2017       -- -fno-common:
2018       --     Don't generate "common" symbols - these are unwanted
2019       --     in dynamic libraries.
2020
2021     | opt_PIC
2022         = ["-fno-common", "-D__PIC__"]
2023     | otherwise
2024         = ["-mdynamic-no-pic"]
2025 #elif mingw32_TARGET_OS
2026       -- no -fPIC for Windows
2027     | opt_PIC
2028         = ["-D__PIC__"]
2029     | otherwise
2030         = []
2031 #else
2032     | opt_PIC
2033         = ["-fPIC", "-D__PIC__"]
2034     | otherwise
2035         = []
2036 #endif
2037
2038 -- -----------------------------------------------------------------------------
2039 -- Splitting
2040
2041 can_split :: Bool
2042 can_split = cSplitObjs == "YES"
2043
2044 -- -----------------------------------------------------------------------------
2045 -- Compiler Info
2046
2047 compilerInfo :: [(String, String)]
2048 compilerInfo = [("Project name",                cProjectName),
2049                 ("Project version",             cProjectVersion),
2050                 ("Booter version",              cBooterVersion),
2051                 ("Stage",                       cStage),
2052                 ("Interface file version",      cHscIfaceFileVersion),
2053                 ("Have interpreter",            cGhcWithInterpreter),
2054                 ("Object splitting",            cSplitObjs),
2055                 ("Have native code generator",  cGhcWithNativeCodeGen),
2056                 ("Support SMP",                 cGhcWithSMP),
2057                 ("Unregisterised",              cGhcUnregisterised),
2058                 ("Tables next to code",         cGhcEnableTablesNextToCode),
2059                 ("Win32 DLLs",                  cEnableWin32DLLs),
2060                 ("RTS ways",                    cGhcRTSWays),
2061                 ("Leading underscore",          cLeadingUnderscore),
2062                 ("Debug on",                    show debugIsOn)
2063                ]
2064