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