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