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