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