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