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