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