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