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