Improve SpecConstr for local bindings: seed specialisation from the calls
[ghc-hetmet.git] / compiler / main / DynFlags.hs
1
2 {-# OPTIONS -fno-warn-missing-fields #-}
3 -- The above warning supression flag is a temporary kludge.
4 -- While working on this module you are encouraged to remove it and fix
5 -- any warnings in the module. See
6 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
7 -- for details
8
9 -----------------------------------------------------------------------------
10 --
11 -- Dynamic flags
12 --
13 -- Most flags are dynamic flags, which means they can change from
14 -- compilation to compilation using OPTIONS_GHC pragmas, and in a
15 -- multi-session GHC each session can be using different dynamic
16 -- flags.  Dynamic flags can also be set at the prompt in GHCi.
17 --
18 -- (c) The University of Glasgow 2005
19 --
20 -----------------------------------------------------------------------------
21
22 module DynFlags (
23         -- Dynamic flags
24         DynFlag(..),
25         DynFlags(..),
26         HscTarget(..), isObjectTarget, defaultObjectTarget,
27         GhcMode(..), isOneShot,
28         GhcLink(..), isNoLink,
29         PackageFlag(..),
30         Option(..),
31         DynLibLoader(..),
32         fFlags, xFlags,
33
34         -- Configuration of the core-to-core and stg-to-stg phases
35         CoreToDo(..),
36         StgToDo(..),
37         SimplifierSwitch(..), 
38         SimplifierMode(..), FloatOutSwitches(..),
39         getCoreToDo, getStgToDo,
40         
41         -- Manipulating DynFlags
42         defaultDynFlags,                -- DynFlags
43         initDynFlags,                   -- DynFlags -> IO DynFlags
44
45         dopt,                           -- DynFlag -> DynFlags -> Bool
46         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
47         getOpts,                        -- (DynFlags -> [a]) -> IO [a]
48         getVerbFlag,
49         updOptLevel,
50         setTmpDir,
51         setPackageName,
52         
53         -- parsing DynFlags
54         parseDynamicFlags,
55         allFlags,
56
57         -- misc stuff
58         machdepCCOpts, picCCOpts,
59     supportedLanguages,
60     compilerInfo,
61   ) where
62
63 -- XXX This define is a bit of a hack, and should be done more nicely
64 #define FAST_STRING_NOT_NEEDED 1
65 #include "HsVersions.h"
66
67 import Module
68 import PackageConfig
69 import PrelNames        ( mAIN )
70 #ifdef i386_TARGET_ARCH
71 import StaticFlags      ( opt_Static )
72 #endif
73 import StaticFlags      ( opt_PIC, WayName(..), v_Ways, v_Build_tag,
74                           v_RTS_Build_tag )
75 import {-# SOURCE #-} Packages (PackageState)
76 import DriverPhases     ( Phase(..), phaseInputExt )
77 import Config
78 import CmdLineParser
79 import Constants        ( mAX_CONTEXT_REDUCTION_DEPTH )
80 import Panic            ( panic, GhcException(..) )
81 import UniqFM           ( UniqFM )
82 import Util
83 import Maybes           ( orElse, fromJust )
84 import SrcLoc           ( SrcSpan )
85 import Outputable
86 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
87
88 import Data.IORef       ( readIORef )
89 import Control.Exception ( throwDyn )
90 import Control.Monad    ( when )
91
92 import Data.Char
93 import System.FilePath
94 import System.IO        ( hPutStrLn, stderr )
95
96 -- -----------------------------------------------------------------------------
97 -- DynFlags
98
99 data DynFlag
100
101    -- debugging flags
102    = Opt_D_dump_cmm
103    | Opt_D_dump_cmmz
104    | Opt_D_dump_cmmz_pretty
105    | Opt_D_dump_cps_cmm
106    | Opt_D_dump_cvt_cmm
107    | Opt_D_dump_asm
108    | Opt_D_dump_asm_native
109    | Opt_D_dump_asm_liveness
110    | Opt_D_dump_asm_coalesce
111    | Opt_D_dump_asm_regalloc
112    | Opt_D_dump_asm_regalloc_stages
113    | Opt_D_dump_asm_conflicts
114    | Opt_D_dump_asm_stats
115    | Opt_D_dump_cpranal
116    | Opt_D_dump_deriv
117    | Opt_D_dump_ds
118    | Opt_D_dump_flatC
119    | Opt_D_dump_foreign
120    | Opt_D_dump_inlinings
121    | Opt_D_dump_rule_firings
122    | Opt_D_dump_occur_anal
123    | Opt_D_dump_parsed
124    | Opt_D_dump_rn
125    | Opt_D_dump_simpl
126    | Opt_D_dump_simpl_iterations
127    | Opt_D_dump_simpl_phases
128    | Opt_D_dump_spec
129    | Opt_D_dump_prep
130    | Opt_D_dump_stg
131    | Opt_D_dump_stranal
132    | Opt_D_dump_tc
133    | Opt_D_dump_types
134    | Opt_D_dump_rules
135    | Opt_D_dump_cse
136    | Opt_D_dump_worker_wrapper
137    | Opt_D_dump_rn_trace
138    | Opt_D_dump_rn_stats
139    | Opt_D_dump_opt_cmm
140    | Opt_D_dump_simpl_stats
141    | Opt_D_dump_tc_trace
142    | Opt_D_dump_if_trace
143    | Opt_D_dump_splices
144    | Opt_D_dump_BCOs
145    | Opt_D_dump_vect
146    | Opt_D_dump_hpc
147    | Opt_D_source_stats
148    | Opt_D_verbose_core2core
149    | Opt_D_verbose_stg2stg
150    | Opt_D_dump_hi
151    | Opt_D_dump_hi_diffs
152    | Opt_D_dump_minimal_imports
153    | Opt_D_dump_mod_cycles
154    | Opt_D_dump_view_pattern_commoning
155    | Opt_D_faststring_stats
156    | Opt_DumpToFile                     -- ^ Append dump output to files instead of stdout.
157    | Opt_DoCoreLinting
158    | Opt_DoStgLinting
159    | Opt_DoCmmLinting
160    | Opt_DoAsmLinting
161
162    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
163    | Opt_WarnDuplicateExports
164    | Opt_WarnHiShadows
165    | Opt_WarnImplicitPrelude
166    | Opt_WarnIncompletePatterns
167    | Opt_WarnIncompletePatternsRecUpd
168    | Opt_WarnMissingFields
169    | Opt_WarnMissingMethods
170    | Opt_WarnMissingSigs
171    | Opt_WarnNameShadowing
172    | Opt_WarnOverlappingPatterns
173    | Opt_WarnSimplePatterns
174    | Opt_WarnTypeDefaults
175    | Opt_WarnMonomorphism
176    | Opt_WarnUnusedBinds
177    | Opt_WarnUnusedImports
178    | Opt_WarnUnusedMatches
179    | Opt_WarnDeprecations
180    | Opt_WarnDodgyImports
181    | Opt_WarnOrphans
182    | Opt_WarnTabs
183
184    -- language opts
185    | Opt_OverlappingInstances
186    | Opt_UndecidableInstances
187    | Opt_IncoherentInstances
188    | Opt_MonomorphismRestriction
189    | Opt_MonoPatBinds
190    | Opt_ExtendedDefaultRules           -- Use GHC's extended rules for defaulting
191    | Opt_ForeignFunctionInterface
192    | Opt_UnliftedFFITypes
193    | Opt_PArr                           -- Syntactic support for parallel arrays
194    | Opt_Arrows                         -- Arrow-notation syntax
195    | Opt_TemplateHaskell
196    | Opt_QuasiQuotes
197    | Opt_ImplicitParams
198    | Opt_Generics
199    | Opt_ImplicitPrelude 
200    | Opt_ScopedTypeVariables
201    | Opt_UnboxedTuples
202    | Opt_BangPatterns
203    | Opt_TypeFamilies
204    | Opt_OverloadedStrings
205    | Opt_DisambiguateRecordFields
206    | Opt_RecordWildCards
207    | Opt_RecordPuns
208    | Opt_ViewPatterns
209    | Opt_GADTs
210    | Opt_RelaxedPolyRec
211    | Opt_StandaloneDeriving
212    | Opt_DeriveDataTypeable
213    | Opt_TypeSynonymInstances
214    | Opt_FlexibleContexts
215    | Opt_FlexibleInstances
216    | Opt_ConstrainedClassMethods
217    | Opt_MultiParamTypeClasses
218    | Opt_FunctionalDependencies
219    | Opt_UnicodeSyntax
220    | Opt_PolymorphicComponents
221    | Opt_ExistentialQuantification
222    | Opt_MagicHash
223    | Opt_EmptyDataDecls
224    | Opt_KindSignatures
225    | Opt_PatternSignatures
226    | Opt_ParallelListComp
227    | Opt_TransformListComp
228    | Opt_GeneralizedNewtypeDeriving
229    | Opt_RecursiveDo
230    | Opt_PatternGuards
231    | Opt_LiberalTypeSynonyms
232    | Opt_Rank2Types
233    | Opt_RankNTypes
234    | Opt_ImpredicativeTypes
235    | Opt_TypeOperators
236
237    | Opt_PrintExplicitForalls
238
239    -- optimisation opts
240    | Opt_Strictness
241    | Opt_FullLaziness
242    | Opt_CSE
243    | Opt_LiberateCase
244    | Opt_SpecConstr
245    | Opt_IgnoreInterfacePragmas
246    | Opt_OmitInterfacePragmas
247    | Opt_DoLambdaEtaExpansion
248    | Opt_IgnoreAsserts
249    | Opt_DoEtaReduction
250    | Opt_CaseMerge
251    | Opt_UnboxStrictFields
252    | Opt_DictsCheap
253    | Opt_RewriteRules
254    | Opt_Vectorise
255    | Opt_RegsGraph                      -- do graph coloring register allocation
256    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
257
258    -- misc opts
259    | Opt_Cpp
260    | Opt_Pp
261    | Opt_ForceRecomp
262    | Opt_DryRun
263    | Opt_DoAsmMangling
264    | Opt_ExcessPrecision
265    | Opt_ReadUserPackageConf
266    | Opt_NoHsMain
267    | Opt_SplitObjs
268    | Opt_StgStats
269    | Opt_HideAllPackages
270    | Opt_PrintBindResult
271    | Opt_Haddock
272    | Opt_HaddockOptions
273    | Opt_Hpc_No_Auto
274    | Opt_BreakOnException
275    | Opt_BreakOnError
276    | Opt_PrintEvldWithShow
277    | Opt_PrintBindContents
278    | Opt_GenManifest
279    | Opt_EmbedManifest
280    | Opt_RunCPSZ
281    | Opt_ConvertToZipCfgAndBack
282
283    -- keeping stuff
284    | Opt_KeepHiDiffs
285    | Opt_KeepHcFiles
286    | Opt_KeepSFiles
287    | Opt_KeepRawSFiles
288    | Opt_KeepTmpFiles
289
290    deriving (Eq, Show)
291  
292 data DynFlags = DynFlags {
293   ghcMode               :: GhcMode,
294   ghcLink               :: GhcLink,
295   coreToDo              :: Maybe [CoreToDo], -- reserved for -Ofile
296   stgToDo               :: Maybe [StgToDo],  -- similarly
297   hscTarget             :: HscTarget,
298   hscOutName            :: String,      -- name of the output file
299   extCoreName           :: String,      -- name of the .core output file
300   verbosity             :: Int,         -- verbosity level
301   optLevel              :: Int,         -- optimisation level
302   simplPhases           :: Int,         -- number of simplifier phases
303   maxSimplIterations    :: Int,         -- max simplifier iterations
304   shouldDumpSimplPhase  :: SimplifierMode -> Bool,
305   ruleCheck             :: Maybe String,
306
307   specConstrThreshold   :: Maybe Int,   -- Threshold for SpecConstr
308   specConstrCount       :: Maybe Int,   -- Max number of specialisations for any one function
309   liberateCaseThreshold :: Maybe Int,   -- Threshold for LiberateCase 
310
311   stolen_x86_regs       :: Int,         
312   cmdlineHcIncludes     :: [String],    -- -#includes
313   importPaths           :: [FilePath],
314   mainModIs             :: Module,
315   mainFunIs             :: Maybe String,
316   ctxtStkDepth          :: Int,         -- Typechecker context stack depth
317
318   thisPackage           :: PackageId,
319
320   -- ways
321   wayNames              :: [WayName],   -- way flags from the cmd line
322   buildTag              :: String,      -- the global "way" (eg. "p" for prof)
323   rtsBuildTag           :: String,      -- the RTS "way"
324   
325   -- paths etc.
326   objectDir             :: Maybe String,
327   hiDir                 :: Maybe String,
328   stubDir               :: Maybe String,
329
330   objectSuf             :: String,
331   hcSuf                 :: String,
332   hiSuf                 :: String,
333
334   outputFile            :: Maybe String,
335   outputHi              :: Maybe String,
336   dynLibLoader          :: DynLibLoader,
337
338   -- | This is set by DriverPipeline.runPipeline based on where
339   --    its output is going.
340   dumpPrefix            :: Maybe FilePath,
341
342   -- | Override the dumpPrefix set by runPipeline.
343   --    Set by -ddump-file-prefix
344   dumpPrefixForce       :: Maybe FilePath,
345
346   includePaths          :: [String],
347   libraryPaths          :: [String],
348   frameworkPaths        :: [String],    -- used on darwin only
349   cmdlineFrameworks     :: [String],    -- ditto
350   tmpDir                :: String,      -- no trailing '/'
351   
352   ghcUsagePath          :: FilePath,    -- Filled in by SysTools
353   ghciUsagePath         :: FilePath,    -- ditto
354
355   hpcDir                :: String,      -- ^ path to store the .mix files
356
357   -- options for particular phases
358   opt_L                 :: [String],
359   opt_P                 :: [String],
360   opt_F                 :: [String],
361   opt_c                 :: [String],
362   opt_m                 :: [String],
363   opt_a                 :: [String],
364   opt_l                 :: [String],
365   opt_dep               :: [String],
366   opt_windres           :: [String],
367
368   -- commands for particular phases
369   pgm_L                 :: String,
370   pgm_P                 :: (String,[Option]),
371   pgm_F                 :: String,
372   pgm_c                 :: (String,[Option]),
373   pgm_m                 :: (String,[Option]),
374   pgm_s                 :: (String,[Option]),
375   pgm_a                 :: (String,[Option]),
376   pgm_l                 :: (String,[Option]),
377   pgm_dll               :: (String,[Option]),
378   pgm_T                 :: String,
379   pgm_sysman            :: String,
380   pgm_windres           :: String,
381
382   --  Package flags
383   extraPkgConfs         :: [FilePath],
384   topDir                :: FilePath,    -- filled in by SysTools
385   systemPackageConfig   :: FilePath,    -- ditto
386         -- The -package-conf flags given on the command line, in the order
387         -- they appeared.
388
389   packageFlags          :: [PackageFlag],
390         -- The -package and -hide-package flags from the command-line
391
392   -- Package state
393   -- NB. do not modify this field, it is calculated by 
394   -- Packages.initPackages and Packages.updatePackages.
395   pkgDatabase           :: Maybe (UniqFM PackageConfig),
396   pkgState              :: PackageState,
397
398   -- hsc dynamic flags
399   flags                 :: [DynFlag],
400   
401   -- message output
402   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
403
404   haddockOptions :: Maybe String
405  }
406
407 data HscTarget
408   = HscC
409   | HscAsm
410   | HscJava
411   | HscInterpreted
412   | HscNothing
413   deriving (Eq, Show)
414
415 -- | will this target result in an object file on the disk?
416 isObjectTarget :: HscTarget -> Bool
417 isObjectTarget HscC     = True
418 isObjectTarget HscAsm   = True
419 isObjectTarget _        = False
420
421 -- | The 'GhcMode' tells us whether we're doing multi-module
422 -- compilation (controlled via the "GHC" API) or one-shot
423 -- (single-module) compilation.  This makes a difference primarily to
424 -- the "Finder": in one-shot mode we look for interface files for
425 -- imported modules, but in multi-module mode we look for source files
426 -- in order to check whether they need to be recompiled.
427 data GhcMode
428   = CompManager         -- ^ --make, GHCi, etc.
429   | OneShot             -- ^ ghc -c Foo.hs
430   | MkDepend            -- ^ ghc -M, see Finder for why we need this
431   deriving Eq
432
433 isOneShot :: GhcMode -> Bool
434 isOneShot OneShot = True
435 isOneShot _other  = False
436
437 -- | What kind of linking to do.
438 data GhcLink    -- What to do in the link step, if there is one
439   = NoLink              -- Don't link at all
440   | LinkBinary          -- Link object code into a binary
441   | LinkInMemory        -- Use the in-memory dynamic linker
442   | LinkDynLib          -- Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
443   deriving (Eq, Show)
444
445 isNoLink :: GhcLink -> Bool
446 isNoLink NoLink = True
447 isNoLink _      = False
448
449 data PackageFlag
450   = ExposePackage  String
451   | HidePackage    String
452   | IgnorePackage  String
453   deriving Eq
454
455 defaultHscTarget :: HscTarget
456 defaultHscTarget = defaultObjectTarget
457
458 -- | the 'HscTarget' value corresponding to the default way to create
459 -- object files on the current platform.
460 defaultObjectTarget :: HscTarget
461 defaultObjectTarget
462   | cGhcWithNativeCodeGen == "YES"      =  HscAsm
463   | otherwise                           =  HscC
464
465 data DynLibLoader
466   = Deployable
467   | Wrapped (Maybe String)
468   | SystemDependent
469   deriving Eq
470
471 initDynFlags :: DynFlags -> IO DynFlags
472 initDynFlags dflags = do
473  -- someday these will be dynamic flags
474  ways <- readIORef v_Ways
475  build_tag <- readIORef v_Build_tag
476  rts_build_tag <- readIORef v_RTS_Build_tag
477  return dflags{
478         wayNames        = ways,
479         buildTag        = build_tag,
480         rtsBuildTag     = rts_build_tag
481         }
482
483 defaultDynFlags :: DynFlags
484 defaultDynFlags =
485      DynFlags {
486         ghcMode                 = CompManager,
487         ghcLink                 = LinkBinary,
488         coreToDo                = Nothing,
489         stgToDo                 = Nothing, 
490         hscTarget               = defaultHscTarget, 
491         hscOutName              = "", 
492         extCoreName             = "",
493         verbosity               = 0, 
494         optLevel                = 0,
495         simplPhases             = 2,
496         maxSimplIterations      = 4,
497         shouldDumpSimplPhase    = const False,
498         ruleCheck               = Nothing,
499         specConstrThreshold     = Just 200,
500         specConstrCount         = Just 3,
501         liberateCaseThreshold   = Just 200,
502         stolen_x86_regs         = 4,
503         cmdlineHcIncludes       = [],
504         importPaths             = ["."],
505         mainModIs               = mAIN,
506         mainFunIs               = Nothing,
507         ctxtStkDepth            = mAX_CONTEXT_REDUCTION_DEPTH,
508
509         thisPackage             = mainPackageId,
510
511         objectDir               = Nothing,
512         hiDir                   = Nothing,
513         stubDir                 = Nothing,
514
515         objectSuf               = phaseInputExt StopLn,
516         hcSuf                   = phaseInputExt HCc,
517         hiSuf                   = "hi",
518
519         outputFile              = Nothing,
520         outputHi                = Nothing,
521         dynLibLoader            = Deployable,
522         dumpPrefix              = Nothing,
523         dumpPrefixForce         = Nothing,
524         includePaths            = [],
525         libraryPaths            = [],
526         frameworkPaths          = [],
527         cmdlineFrameworks       = [],
528         tmpDir                  = cDEFAULT_TMPDIR,
529         
530         hpcDir                  = ".hpc",
531
532         opt_L                   = [],
533         opt_P                   = (if opt_PIC
534                                    then ["-D__PIC__"]
535                                    else []),
536         opt_F                   = [],
537         opt_c                   = [],
538         opt_a                   = [],
539         opt_m                   = [],
540         opt_l                   = [],
541         opt_dep                 = [],
542         opt_windres             = [],
543         
544         extraPkgConfs           = [],
545         packageFlags            = [],
546         pkgDatabase             = Nothing,
547         pkgState                = panic "no package state yet: call GHC.setSessionDynFlags",
548   haddockOptions = Nothing,
549         flags = [
550             Opt_ReadUserPackageConf,
551
552             Opt_MonoPatBinds,   -- Experimentally, I'm making this non-standard
553                                 -- behaviour the default, to see if anyone notices
554                                 -- SLPJ July 06
555
556             Opt_ImplicitPrelude,
557             Opt_MonomorphismRestriction,
558
559             Opt_DoAsmMangling,
560
561             Opt_GenManifest,
562             Opt_EmbedManifest,
563             Opt_PrintBindContents
564             ]
565             ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
566                     -- The default -O0 options
567             ++ standardWarnings,
568
569         log_action = \severity srcSpan style msg -> 
570                         case severity of
571                           SevInfo  -> hPutStrLn stderr (show (msg style))
572                           SevFatal -> hPutStrLn stderr (show (msg style))
573                           _        -> hPutStrLn stderr ('\n':show ((mkLocMessage srcSpan msg) style))
574       }
575
576 {- 
577     Verbosity levels:
578         
579     0   |   print errors & warnings only
580     1   |   minimal verbosity: print "compiling M ... done." for each module.
581     2   |   equivalent to -dshow-passes
582     3   |   equivalent to existing "ghc -v"
583     4   |   "ghc -v -ddump-most"
584     5   |   "ghc -v -ddump-all"
585 -}
586
587 dopt :: DynFlag -> DynFlags -> Bool
588 dopt f dflags  = f `elem` (flags dflags)
589
590 dopt_set :: DynFlags -> DynFlag -> DynFlags
591 dopt_set dfs f = dfs{ flags = f : flags dfs }
592
593 dopt_unset :: DynFlags -> DynFlag -> DynFlags
594 dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
595
596 getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
597 getOpts dflags opts = reverse (opts dflags)
598         -- We add to the options from the front, so we need to reverse the list
599
600 getVerbFlag :: DynFlags -> String
601 getVerbFlag dflags 
602   | verbosity dflags >= 3  = "-v" 
603   | otherwise =  ""
604
605 setObjectDir, setHiDir, setStubDir, setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
606          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
607          addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptdep, addOptwindres,
608          addCmdlineFramework, addHaddockOpts
609    :: String -> DynFlags -> DynFlags
610 setOutputFile, setOutputHi, setDumpPrefixForce
611    :: Maybe String -> DynFlags -> DynFlags
612
613 setObjectDir  f d = d{ objectDir  = Just f}
614 setHiDir      f d = d{ hiDir      = Just f}
615 setStubDir    f d = d{ stubDir    = Just f, includePaths = f : includePaths d }
616   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
617   -- #included from the .hc file when compiling with -fvia-C.
618
619 setObjectSuf  f d = d{ objectSuf  = f}
620 setHiSuf      f d = d{ hiSuf      = f}
621 setHcSuf      f d = d{ hcSuf      = f}
622
623 setOutputFile f d = d{ outputFile = f}
624 setOutputHi   f d = d{ outputHi   = f}
625
626 parseDynLibLoaderMode f d =
627  case splitAt 8 f of
628    ("deploy", "")       -> d{ dynLibLoader = Deployable }
629    ("sysdep", "")       -> d{ dynLibLoader = SystemDependent }
630    ("wrapped", "")      -> d{ dynLibLoader = Wrapped Nothing }
631    ("wrapped:", "hard") -> d{ dynLibLoader = Wrapped Nothing }
632    ("wrapped:", flex)   -> d{ dynLibLoader = Wrapped (Just flex) }
633    (_,_)                -> error "Unknown dynlib loader"
634
635 setDumpPrefixForce f d = d { dumpPrefixForce = f}
636
637 -- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
638 -- Config.hs should really use Option.
639 setPgmP   f d = let (pgm:args) = words f in d{ pgm_P   = (pgm, map Option args)}
640
641 setPgmL   f d = d{ pgm_L   = f}
642 setPgmF   f d = d{ pgm_F   = f}
643 setPgmc   f d = d{ pgm_c   = (f,[])}
644 setPgmm   f d = d{ pgm_m   = (f,[])}
645 setPgms   f d = d{ pgm_s   = (f,[])}
646 setPgma   f d = d{ pgm_a   = (f,[])}
647 setPgml   f d = d{ pgm_l   = (f,[])}
648 setPgmdll f d = d{ pgm_dll = (f,[])}
649 setPgmwindres f d = d{ pgm_windres = f}
650
651 addOptL   f d = d{ opt_L   = f : opt_L d}
652 addOptP   f d = d{ opt_P   = f : opt_P d}
653 addOptF   f d = d{ opt_F   = f : opt_F d}
654 addOptc   f d = d{ opt_c   = f : opt_c d}
655 addOptm   f d = d{ opt_m   = f : opt_m d}
656 addOpta   f d = d{ opt_a   = f : opt_a d}
657 addOptl   f d = d{ opt_l   = f : opt_l d}
658 addOptdep f d = d{ opt_dep = f : opt_dep d}
659 addOptwindres f d = d{ opt_windres = f : opt_windres d}
660
661 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
662
663 addHaddockOpts f d = d{ haddockOptions = Just f}
664
665 -- -----------------------------------------------------------------------------
666 -- Command-line options
667
668 -- When invoking external tools as part of the compilation pipeline, we
669 -- pass these a sequence of options on the command-line. Rather than
670 -- just using a list of Strings, we use a type that allows us to distinguish
671 -- between filepaths and 'other stuff'. [The reason being, of course, that
672 -- this type gives us a handle on transforming filenames, and filenames only,
673 -- to whatever format they're expected to be on a particular platform.]
674
675 data Option
676  = FileOption -- an entry that _contains_ filename(s) / filepaths.
677               String  -- a non-filepath prefix that shouldn't be 
678                       -- transformed (e.g., "/out=")
679               String  -- the filepath/filename portion
680  | Option     String
681  
682 -----------------------------------------------------------------------------
683 -- Setting the optimisation level
684
685 updOptLevel :: Int -> DynFlags -> DynFlags
686 -- Set dynflags appropriate to the optimisation level
687 updOptLevel n dfs
688   = dfs2{ optLevel = final_n }
689   where
690    final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
691    dfs1 = foldr (flip dopt_unset) dfs  remove_dopts
692    dfs2 = foldr (flip dopt_set)   dfs1 extra_dopts
693
694    extra_dopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
695    remove_dopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
696         
697 optLevelFlags :: [([Int], DynFlag)]
698 optLevelFlags
699   = [ ([0],     Opt_IgnoreInterfacePragmas)
700     , ([0],     Opt_OmitInterfacePragmas)
701
702     , ([1,2],   Opt_IgnoreAsserts)
703     , ([1,2],   Opt_RewriteRules)       -- Off for -O0; see Note [Scoping for Builtin rules]
704                                         --              in PrelRules
705     , ([1,2],   Opt_DoEtaReduction)
706     , ([1,2],   Opt_CaseMerge)
707     , ([1,2],   Opt_Strictness)
708     , ([1,2],   Opt_CSE)
709     , ([1,2],   Opt_FullLaziness)
710
711     , ([2],     Opt_LiberateCase)
712     , ([2],     Opt_SpecConstr)
713
714     , ([0,1,2], Opt_DoLambdaEtaExpansion)
715                 -- This one is important for a tiresome reason:
716                 -- we want to make sure that the bindings for data 
717                 -- constructors are eta-expanded.  This is probably
718                 -- a good thing anyway, but it seems fragile.
719     ]
720
721 -- -----------------------------------------------------------------------------
722 -- Standard sets of warning options
723
724 standardWarnings :: [DynFlag]
725 standardWarnings
726     = [ Opt_WarnDeprecations,
727         Opt_WarnOverlappingPatterns,
728         Opt_WarnMissingFields,
729         Opt_WarnMissingMethods,
730         Opt_WarnDuplicateExports
731       ]
732
733 minusWOpts :: [DynFlag]
734 minusWOpts
735     = standardWarnings ++ 
736       [ Opt_WarnUnusedBinds,
737         Opt_WarnUnusedMatches,
738         Opt_WarnUnusedImports,
739         Opt_WarnIncompletePatterns,
740         Opt_WarnDodgyImports
741       ]
742
743 minusWallOpts :: [DynFlag]
744 minusWallOpts
745     = minusWOpts ++
746       [ Opt_WarnTypeDefaults,
747         Opt_WarnNameShadowing,
748         Opt_WarnMissingSigs,
749         Opt_WarnHiShadows,
750         Opt_WarnOrphans
751       ]
752
753 -- minuswRemovesOpts should be every warning option
754 minuswRemovesOpts :: [DynFlag]
755 minuswRemovesOpts
756     = minusWallOpts ++
757       [Opt_WarnImplicitPrelude,
758        Opt_WarnIncompletePatternsRecUpd,
759        Opt_WarnSimplePatterns,
760        Opt_WarnMonomorphism,
761        Opt_WarnTabs
762       ]
763
764 -- -----------------------------------------------------------------------------
765 -- CoreToDo:  abstraction of core-to-core passes to run.
766
767 data CoreToDo           -- These are diff core-to-core passes,
768                         -- which may be invoked in any order,
769                         -- as many times as you like.
770
771   = CoreDoSimplify      -- The core-to-core simplifier.
772         SimplifierMode
773         [SimplifierSwitch]
774                         -- Each run of the simplifier can take a different
775                         -- set of simplifier-specific flags.
776   | CoreDoFloatInwards
777   | CoreDoFloatOutwards FloatOutSwitches
778   | CoreLiberateCase
779   | CoreDoPrintCore
780   | CoreDoStaticArgs
781   | CoreDoStrictness
782   | CoreDoWorkerWrapper
783   | CoreDoSpecialising
784   | CoreDoSpecConstr
785   | CoreDoOldStrictness
786   | CoreDoGlomBinds
787   | CoreCSE
788   | CoreDoRuleCheck Int{-CompilerPhase-} String -- Check for non-application of rules 
789                                                 -- matching this string
790   | CoreDoVectorisation
791   | CoreDoNothing                -- Useful when building up 
792   | CoreDoPasses [CoreToDo]      -- lists of these things
793
794 data SimplifierMode             -- See comments in SimplMonad
795   = SimplGently
796   | SimplPhase Int [String]
797
798 data SimplifierSwitch
799   = MaxSimplifierIterations Int
800   | NoCaseOfCase
801
802 data FloatOutSwitches
803   = FloatOutSw  Bool    -- True <=> float lambdas to top level
804                 Bool    -- True <=> float constants to top level,
805                         --          even if they do not escape a lambda
806
807
808 -- The core-to-core pass ordering is derived from the DynFlags:
809 runWhen :: Bool -> CoreToDo -> CoreToDo
810 runWhen True  do_this = do_this
811 runWhen False _       = CoreDoNothing
812
813 runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo
814 runMaybe (Just x) f = f x
815 runMaybe Nothing  _ = CoreDoNothing
816
817 getCoreToDo :: DynFlags -> [CoreToDo]
818 getCoreToDo dflags
819   | Just todo <- coreToDo dflags = todo -- set explicitly by user
820   | otherwise = core_todo
821   where
822     opt_level     = optLevel dflags
823     phases        = simplPhases dflags
824     max_iter      = maxSimplIterations dflags
825     strictness    = dopt Opt_Strictness dflags
826     full_laziness = dopt Opt_FullLaziness dflags
827     cse           = dopt Opt_CSE dflags
828     spec_constr   = dopt Opt_SpecConstr dflags
829     liberate_case = dopt Opt_LiberateCase dflags
830     rule_check    = ruleCheck dflags
831     vectorisation = dopt Opt_Vectorise dflags
832
833     maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase)
834
835     simpl_phase phase names iter
836       = CoreDoPasses
837           [ CoreDoSimplify (SimplPhase phase names) [
838               MaxSimplifierIterations iter
839             ],
840             maybe_rule_check phase
841           ]
842
843                 -- By default, we have 2 phases before phase 0.
844
845                 -- Want to run with inline phase 2 after the specialiser to give
846                 -- maximum chance for fusion to work before we inline build/augment
847                 -- in phase 1.  This made a difference in 'ansi' where an 
848                 -- overloaded function wasn't inlined till too late.
849
850                 -- Need phase 1 so that build/augment get 
851                 -- inlined.  I found that spectral/hartel/genfft lost some useful
852                 -- strictness in the function sumcode' if augment is not inlined
853                 -- before strictness analysis runs
854     simpl_phases = CoreDoPasses [ simpl_phase phase ["main"] max_iter
855                                   | phase <- [phases, phases-1 .. 1] ]
856
857
858         -- initial simplify: mk specialiser happy: minimum effort please
859     simpl_gently = CoreDoSimplify SimplGently [
860                         --      Simplify "gently"
861                         -- Don't inline anything till full laziness has bitten
862                         -- In particular, inlining wrappers inhibits floating
863                         -- e.g. ...(case f x of ...)...
864                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
865                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
866                         -- and now the redex (f x) isn't floatable any more
867                         -- Similarly, don't apply any rules until after full 
868                         -- laziness.  Notably, list fusion can prevent floating.
869
870             NoCaseOfCase,       -- Don't do case-of-case transformations.
871                                 -- This makes full laziness work better
872             MaxSimplifierIterations max_iter
873         ]
874
875     core_todo = 
876      if opt_level == 0 then
877        [simpl_phase 0 ["final"] max_iter]
878      else {- opt_level >= 1 -} [ 
879
880         -- initial simplify: mk specialiser happy: minimum effort please
881         simpl_gently,
882
883         -- We run vectorisation here for now, but we might also try to run
884         -- it later
885         runWhen vectorisation (CoreDoPasses [ CoreDoVectorisation, simpl_gently ]),
886
887         -- Specialisation is best done before full laziness
888         -- so that overloaded functions have all their dictionary lambdas manifest
889         CoreDoSpecialising,
890
891         runWhen full_laziness (CoreDoFloatOutwards (FloatOutSw False False)),
892
893         CoreDoFloatInwards,
894
895         simpl_phases,
896
897                 -- Phase 0: allow all Ids to be inlined now
898                 -- This gets foldr inlined before strictness analysis
899
900                 -- At least 3 iterations because otherwise we land up with
901                 -- huge dead expressions because of an infelicity in the 
902                 -- simpifier.   
903                 --      let k = BIG in foldr k z xs
904                 -- ==>  let k = BIG in letrec go = \xs -> ...(k x).... in go xs
905                 -- ==>  let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs
906                 -- Don't stop now!
907         simpl_phase 0 ["main"] (max max_iter 3),
908
909
910 #ifdef OLD_STRICTNESS
911         CoreDoOldStrictness,
912 #endif
913         runWhen strictness (CoreDoPasses [
914                 CoreDoStrictness,
915                 CoreDoWorkerWrapper,
916                 CoreDoGlomBinds,
917                 simpl_phase 0 ["post-worker-wrapper"] max_iter
918                 ]),
919
920         runWhen full_laziness 
921           (CoreDoFloatOutwards (FloatOutSw False    -- Not lambdas
922                                            True)),  -- Float constants
923                 -- nofib/spectral/hartel/wang doubles in speed if you
924                 -- do full laziness late in the day.  It only happens
925                 -- after fusion and other stuff, so the early pass doesn't
926                 -- catch it.  For the record, the redex is 
927                 --        f_el22 (f_el21 r_midblock)
928
929
930         runWhen cse CoreCSE,
931                 -- We want CSE to follow the final full-laziness pass, because it may
932                 -- succeed in commoning up things floated out by full laziness.
933                 -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
934
935         CoreDoFloatInwards,
936
937         maybe_rule_check 0,
938
939                 -- Case-liberation for -O2.  This should be after
940                 -- strictness analysis and the simplification which follows it.
941         runWhen liberate_case (CoreDoPasses [
942             CoreLiberateCase,
943             simpl_phase 0 ["post-liberate-case"] max_iter
944             ]),         -- Run the simplifier after LiberateCase to vastly 
945                         -- reduce the possiblility of shadowing
946                         -- Reason: see Note [Shadowing] in SpecConstr.lhs
947
948         runWhen spec_constr CoreDoSpecConstr,
949
950         maybe_rule_check 0,
951
952         -- Final clean-up simplification:
953         simpl_phase 0 ["final"] max_iter
954      ]
955
956 -- -----------------------------------------------------------------------------
957 -- StgToDo:  abstraction of stg-to-stg passes to run.
958
959 data StgToDo
960   = StgDoMassageForProfiling  -- should be (next to) last
961   -- There's also setStgVarInfo, but its absolute "lastness"
962   -- is so critical that it is hardwired in (no flag).
963   | D_stg_stats
964
965 getStgToDo :: DynFlags -> [StgToDo]
966 getStgToDo dflags
967   | Just todo <- stgToDo dflags = todo -- set explicitly by user
968   | otherwise = todo2
969   where
970         stg_stats = dopt Opt_StgStats dflags
971
972         todo1 = if stg_stats then [D_stg_stats] else []
973
974         todo2 | WayProf `elem` wayNames dflags
975               = StgDoMassageForProfiling : todo1
976               | otherwise
977               = todo1
978
979 -- -----------------------------------------------------------------------------
980 -- DynFlags parser
981
982 allFlags :: [String]
983 allFlags = map ('-':) $
984            [ name | (name, optkind) <- dynamic_flags, ok optkind ] ++
985            map ("fno-"++) flags ++
986            map ("f"++) flags ++
987            map ("X"++) xs ++
988            map ("XNo"++) xs
989     where ok (PrefixPred _ _) = False
990           ok _ = True
991           flags = map fst fFlags
992           xs = map fst xFlags
993
994 dynamic_flags :: [(String, OptKind DynP)]
995 dynamic_flags = [
996      ( "n"              , NoArg  (setDynFlag Opt_DryRun) )
997   ,  ( "cpp"            , NoArg  (setDynFlag Opt_Cpp))
998   ,  ( "F"              , NoArg  (setDynFlag Opt_Pp))
999   ,  ( "#include"       , HasArg (addCmdlineHCInclude) )
1000   ,  ( "v"              , OptIntSuffix setVerbosity )
1001
1002         ------- Specific phases  --------------------------------------------
1003   ,  ( "pgmL"           , HasArg (upd . setPgmL) )  
1004   ,  ( "pgmP"           , HasArg (upd . setPgmP) )  
1005   ,  ( "pgmF"           , HasArg (upd . setPgmF) )  
1006   ,  ( "pgmc"           , HasArg (upd . setPgmc) )  
1007   ,  ( "pgmm"           , HasArg (upd . setPgmm) )  
1008   ,  ( "pgms"           , HasArg (upd . setPgms) )  
1009   ,  ( "pgma"           , HasArg (upd . setPgma) )  
1010   ,  ( "pgml"           , HasArg (upd . setPgml) )  
1011   ,  ( "pgmdll"         , HasArg (upd . setPgmdll) )
1012   ,  ( "pgmwindres"     , HasArg (upd . setPgmwindres) )
1013
1014   ,  ( "optL"           , HasArg (upd . addOptL) )  
1015   ,  ( "optP"           , HasArg (upd . addOptP) )  
1016   ,  ( "optF"           , HasArg (upd . addOptF) )  
1017   ,  ( "optc"           , HasArg (upd . addOptc) )  
1018   ,  ( "optm"           , HasArg (upd . addOptm) )  
1019   ,  ( "opta"           , HasArg (upd . addOpta) )  
1020   ,  ( "optl"           , HasArg (upd . addOptl) )  
1021   ,  ( "optdep"         , HasArg (upd . addOptdep) )
1022   ,  ( "optwindres"     , HasArg (upd . addOptwindres) )
1023
1024   ,  ( "split-objs"     , NoArg (if can_split
1025                                     then setDynFlag Opt_SplitObjs
1026                                     else return ()) )
1027
1028         -------- Linking ----------------------------------------------------
1029   ,  ( "c"              , NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
1030   ,  ( "no-link"        , NoArg (upd $ \d -> d{ ghcLink=NoLink } )) -- Dep.
1031   ,  ( "shared"         , NoArg (upd $ \d -> d{ ghcLink=LinkDynLib } ))
1032   ,  ( "dynload"        , HasArg (upd . parseDynLibLoaderMode))
1033
1034         ------- Libraries ---------------------------------------------------
1035   ,  ( "L"              , Prefix addLibraryPath )
1036   ,  ( "l"              , AnySuffix (\s -> do upd (addOptl s)))
1037
1038         ------- Frameworks --------------------------------------------------
1039         -- -framework-path should really be -F ...
1040   ,  ( "framework-path" , HasArg addFrameworkPath )
1041   ,  ( "framework"      , HasArg (upd . addCmdlineFramework) )
1042
1043         ------- Output Redirection ------------------------------------------
1044   ,  ( "odir"           , HasArg (upd . setObjectDir))
1045   ,  ( "o"              , SepArg (upd . setOutputFile . Just))
1046   ,  ( "ohi"            , HasArg (upd . setOutputHi   . Just ))
1047   ,  ( "osuf"           , HasArg (upd . setObjectSuf))
1048   ,  ( "hcsuf"          , HasArg (upd . setHcSuf))
1049   ,  ( "hisuf"          , HasArg (upd . setHiSuf))
1050   ,  ( "hidir"          , HasArg (upd . setHiDir))
1051   ,  ( "tmpdir"         , HasArg (upd . setTmpDir))
1052   ,  ( "stubdir"        , HasArg (upd . setStubDir))
1053   ,  ( "ddump-file-prefix", HasArg (upd . setDumpPrefixForce . Just))
1054
1055         ------- Keeping temporary files -------------------------------------
1056      -- These can be singular (think ghc -c) or plural (think ghc --make)
1057   ,  ( "keep-hc-file"    , NoArg (setDynFlag Opt_KeepHcFiles))
1058   ,  ( "keep-hc-files"   , NoArg (setDynFlag Opt_KeepHcFiles))
1059   ,  ( "keep-s-file"     , NoArg (setDynFlag Opt_KeepSFiles))
1060   ,  ( "keep-s-files"    , NoArg (setDynFlag Opt_KeepSFiles))
1061   ,  ( "keep-raw-s-file" , NoArg (setDynFlag Opt_KeepRawSFiles))
1062   ,  ( "keep-raw-s-files", NoArg (setDynFlag Opt_KeepRawSFiles))
1063      -- This only makes sense as plural
1064   ,  ( "keep-tmp-files"  , NoArg (setDynFlag Opt_KeepTmpFiles))
1065
1066         ------- Miscellaneous ----------------------------------------------
1067   ,  ( "no-hs-main"     , NoArg (setDynFlag Opt_NoHsMain))
1068   ,  ( "main-is"        , SepArg setMainIs )
1069   ,  ( "haddock"        , NoArg (setDynFlag Opt_Haddock) )
1070   ,  ( "haddock-opts"   , HasArg (upd . addHaddockOpts))
1071   ,  ( "hpcdir"         , SepArg setOptHpcDir )
1072
1073         ------- recompilation checker (DEPRECATED, use -fforce-recomp) -----
1074   ,  ( "recomp"         , NoArg (unSetDynFlag Opt_ForceRecomp) )
1075   ,  ( "no-recomp"      , NoArg (setDynFlag   Opt_ForceRecomp) )
1076
1077         ------- Packages ----------------------------------------------------
1078   ,  ( "package-conf"   , HasArg extraPkgConf_ )
1079   ,  ( "no-user-package-conf", NoArg (unSetDynFlag Opt_ReadUserPackageConf) )
1080   ,  ( "package-name"   , HasArg (upd . setPackageName) )
1081   ,  ( "package"        , HasArg exposePackage )
1082   ,  ( "hide-package"   , HasArg hidePackage )
1083   ,  ( "hide-all-packages", NoArg (setDynFlag Opt_HideAllPackages) )
1084   ,  ( "ignore-package" , HasArg ignorePackage )
1085   ,  ( "syslib"         , HasArg exposePackage )  -- for compatibility
1086
1087         ------ HsCpp opts ---------------------------------------------------
1088   ,  ( "D",             AnySuffix (upd . addOptP) )
1089   ,  ( "U",             AnySuffix (upd . addOptP) )
1090
1091         ------- Include/Import Paths ----------------------------------------
1092   ,  ( "I"              , Prefix    addIncludePath)
1093   ,  ( "i"              , OptPrefix addImportPath )
1094
1095         ------ Debugging ----------------------------------------------------
1096   ,  ( "dstg-stats",    NoArg (setDynFlag Opt_StgStats))
1097
1098   ,  ( "ddump-cmm",              setDumpFlag Opt_D_dump_cmm)
1099   ,  ( "ddump-cmmz",             setDumpFlag Opt_D_dump_cmmz)
1100   ,  ( "ddump-cmmz-pretty",      setDumpFlag Opt_D_dump_cmmz_pretty)
1101   ,  ( "ddump-cps-cmm",          setDumpFlag Opt_D_dump_cps_cmm)
1102   ,  ( "ddump-cvt-cmm",          setDumpFlag Opt_D_dump_cvt_cmm)
1103   ,  ( "ddump-asm",              setDumpFlag Opt_D_dump_asm)
1104   ,  ( "ddump-asm-native",       setDumpFlag Opt_D_dump_asm_native)
1105   ,  ( "ddump-asm-liveness",     setDumpFlag Opt_D_dump_asm_liveness)
1106   ,  ( "ddump-asm-coalesce",     setDumpFlag Opt_D_dump_asm_coalesce)
1107   ,  ( "ddump-asm-regalloc",     setDumpFlag Opt_D_dump_asm_regalloc)
1108   ,  ( "ddump-asm-conflicts",    setDumpFlag Opt_D_dump_asm_conflicts)
1109   ,  ( "ddump-asm-regalloc-stages",
1110                                  setDumpFlag Opt_D_dump_asm_regalloc_stages)
1111   ,  ( "ddump-asm-stats",        setDumpFlag Opt_D_dump_asm_stats)
1112   ,  ( "ddump-cpranal",          setDumpFlag Opt_D_dump_cpranal)
1113   ,  ( "ddump-deriv",            setDumpFlag Opt_D_dump_deriv)
1114   ,  ( "ddump-ds",               setDumpFlag Opt_D_dump_ds)
1115   ,  ( "ddump-flatC",            setDumpFlag Opt_D_dump_flatC)
1116   ,  ( "ddump-foreign",          setDumpFlag Opt_D_dump_foreign)
1117   ,  ( "ddump-inlinings",        setDumpFlag Opt_D_dump_inlinings)
1118   ,  ( "ddump-rule-firings",     setDumpFlag Opt_D_dump_rule_firings)
1119   ,  ( "ddump-occur-anal",       setDumpFlag Opt_D_dump_occur_anal)
1120   ,  ( "ddump-parsed",           setDumpFlag Opt_D_dump_parsed)
1121   ,  ( "ddump-rn",               setDumpFlag Opt_D_dump_rn)
1122   ,  ( "ddump-simpl",            setDumpFlag Opt_D_dump_simpl)
1123   ,  ( "ddump-simpl-iterations", setDumpFlag Opt_D_dump_simpl_iterations)
1124   ,  ( "ddump-simpl-phases",     OptPrefix setDumpSimplPhases)
1125   ,  ( "ddump-spec",             setDumpFlag Opt_D_dump_spec)
1126   ,  ( "ddump-prep",             setDumpFlag Opt_D_dump_prep)
1127   ,  ( "ddump-stg",              setDumpFlag Opt_D_dump_stg)
1128   ,  ( "ddump-stranal",          setDumpFlag Opt_D_dump_stranal)
1129   ,  ( "ddump-tc",               setDumpFlag Opt_D_dump_tc)
1130   ,  ( "ddump-types",            setDumpFlag Opt_D_dump_types)
1131   ,  ( "ddump-rules",            setDumpFlag Opt_D_dump_rules)
1132   ,  ( "ddump-cse",              setDumpFlag Opt_D_dump_cse)
1133   ,  ( "ddump-worker-wrapper",   setDumpFlag Opt_D_dump_worker_wrapper)
1134   ,  ( "ddump-rn-trace",         setDumpFlag Opt_D_dump_rn_trace)
1135   ,  ( "ddump-if-trace",         setDumpFlag Opt_D_dump_if_trace)
1136   ,  ( "ddump-tc-trace",         setDumpFlag Opt_D_dump_tc_trace)
1137   ,  ( "ddump-splices",          setDumpFlag Opt_D_dump_splices)
1138   ,  ( "ddump-rn-stats",         setDumpFlag Opt_D_dump_rn_stats)
1139   ,  ( "ddump-opt-cmm",          setDumpFlag Opt_D_dump_opt_cmm)
1140   ,  ( "ddump-simpl-stats",      setDumpFlag Opt_D_dump_simpl_stats)
1141   ,  ( "ddump-bcos",             setDumpFlag Opt_D_dump_BCOs)
1142   ,  ( "dsource-stats",          setDumpFlag Opt_D_source_stats)
1143   ,  ( "dverbose-core2core",     NoArg setVerboseCore2Core)
1144   ,  ( "dverbose-stg2stg",       setDumpFlag Opt_D_verbose_stg2stg)
1145   ,  ( "ddump-hi",               setDumpFlag Opt_D_dump_hi)
1146   ,  ( "ddump-minimal-imports",  setDumpFlag Opt_D_dump_minimal_imports)
1147   ,  ( "ddump-vect",             setDumpFlag Opt_D_dump_vect)
1148   ,  ( "ddump-hpc",              setDumpFlag Opt_D_dump_hpc)
1149   ,  ( "ddump-mod-cycles",       setDumpFlag Opt_D_dump_mod_cycles)
1150   ,  ( "ddump-view-pattern-commoning", setDumpFlag Opt_D_dump_view_pattern_commoning)
1151   ,  ( "ddump-to-file",          setDumpFlag Opt_DumpToFile)
1152   ,  ( "ddump-hi-diffs",         NoArg (setDynFlag Opt_D_dump_hi_diffs))
1153   ,  ( "dcore-lint",             NoArg (setDynFlag Opt_DoCoreLinting))
1154   ,  ( "dstg-lint",              NoArg (setDynFlag Opt_DoStgLinting))
1155   ,  ( "dcmm-lint",              NoArg (setDynFlag Opt_DoCmmLinting))
1156   ,  ( "dasm-lint",              NoArg (setDynFlag Opt_DoAsmLinting))
1157   ,  ( "dshow-passes",           NoArg (do setDynFlag Opt_ForceRecomp
1158                                            setVerbosity (Just 2)) )
1159   ,  ( "dfaststring-stats",      NoArg (setDynFlag Opt_D_faststring_stats))
1160
1161         ------ Machine dependant (-m<blah>) stuff ---------------------------
1162
1163   ,  ( "monly-2-regs",  NoArg (upd (\s -> s{stolen_x86_regs = 2}) ))
1164   ,  ( "monly-3-regs",  NoArg (upd (\s -> s{stolen_x86_regs = 3}) ))
1165   ,  ( "monly-4-regs",  NoArg (upd (\s -> s{stolen_x86_regs = 4}) ))
1166
1167      ------ Warning opts -------------------------------------------------
1168   ,  ( "W"     , NoArg (mapM_ setDynFlag   minusWOpts)    )
1169   ,  ( "Werror", NoArg (setDynFlag         Opt_WarnIsError) )
1170   ,  ( "Wwarn" , NoArg (unSetDynFlag       Opt_WarnIsError) )
1171   ,  ( "Wall"  , NoArg (mapM_ setDynFlag   minusWallOpts) )
1172   ,  ( "Wnot"  , NoArg (mapM_ unSetDynFlag minusWallOpts) ) -- DEPRECATED
1173   ,  ( "w"     , NoArg (mapM_ unSetDynFlag minuswRemovesOpts) )
1174
1175         ------ Optimisation flags ------------------------------------------
1176   ,  ( "O"      , NoArg (upd (setOptLevel 1)))
1177   ,  ( "Onot"   , NoArg (upd (setOptLevel 0))) -- deprecated
1178   ,  ( "O"      , OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1))))
1179                 -- If the number is missing, use 1
1180
1181   ,  ( "fsimplifier-phases",         IntSuffix (\n ->
1182                 upd (\dfs -> dfs{ simplPhases = n })) )
1183   ,  ( "fmax-simplifier-iterations", IntSuffix (\n -> 
1184                 upd (\dfs -> dfs{ maxSimplIterations = n })) )
1185
1186   ,  ( "fspec-constr-threshold",      IntSuffix (\n ->
1187                 upd (\dfs -> dfs{ specConstrThreshold = Just n })))
1188   ,  ( "fno-spec-constr-threshold",   NoArg (
1189                 upd (\dfs -> dfs{ specConstrThreshold = Nothing })))
1190   ,  ( "fspec-constr-count",          IntSuffix (\n ->
1191                 upd (\dfs -> dfs{ specConstrCount = Just n })))
1192   ,  ( "fno-spec-constr-count",   NoArg (
1193                 upd (\dfs -> dfs{ specConstrCount = Nothing })))
1194   ,  ( "fliberate-case-threshold",    IntSuffix (\n ->
1195                 upd (\dfs -> dfs{ liberateCaseThreshold = Just n })))
1196   ,  ( "fno-liberate-case-threshold", NoArg (
1197                 upd (\dfs -> dfs{ liberateCaseThreshold = Nothing })))
1198
1199   ,  ( "frule-check",     SepArg (\s -> upd (\dfs -> dfs{ ruleCheck = Just s })))
1200   ,  ( "fcontext-stack" , IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
1201
1202         ------ Compiler flags -----------------------------------------------
1203
1204   ,  ( "fasm",             NoArg (setObjTarget HscAsm) )
1205   ,  ( "fvia-c",           NoArg (setObjTarget HscC) )
1206   ,  ( "fvia-C",           NoArg (setObjTarget HscC) )
1207
1208   ,  ( "fno-code",         NoArg (setTarget HscNothing))
1209   ,  ( "fbyte-code",       NoArg (setTarget HscInterpreted) )
1210   ,  ( "fobject-code",     NoArg (setTarget defaultHscTarget) )
1211
1212   ,  ( "fglasgow-exts",    NoArg (mapM_ setDynFlag   glasgowExtsFlags) )
1213   ,  ( "fno-glasgow-exts", NoArg (mapM_ unSetDynFlag glasgowExtsFlags) )
1214
1215      -- the rest of the -f* and -fno-* flags
1216   ,  ( "f",                PrefixPred (isFlag   fFlags)
1217                            (\f -> setDynFlag   (getFlag   fFlags f)) )
1218   ,  ( "f",                PrefixPred (isPrefFlag "no-" fFlags)
1219                            (\f -> unSetDynFlag (getPrefFlag "no-" fFlags f)) )
1220
1221      -- the -X* and -XNo* flags
1222   ,  ( "X",                PrefixPred (isFlag   xFlags)
1223                            (\f -> setDynFlag   (getFlag   xFlags f)) )
1224   ,  ( "X",                PrefixPred (isPrefFlag "No" xFlags)
1225                            (\f -> unSetDynFlag (getPrefFlag "No" xFlags f)) )
1226  ]
1227
1228 -- these -f<blah> flags can all be reversed with -fno-<blah>
1229
1230 fFlags :: [(String, DynFlag)]
1231 fFlags = [
1232   ( "warn-dodgy-imports",               Opt_WarnDodgyImports ),
1233   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports ),
1234   ( "warn-hi-shadowing",                Opt_WarnHiShadows ),
1235   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude ),
1236   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns ),
1237   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd ),
1238   ( "warn-missing-fields",              Opt_WarnMissingFields ),
1239   ( "warn-missing-methods",             Opt_WarnMissingMethods ),
1240   ( "warn-missing-signatures",          Opt_WarnMissingSigs ),
1241   ( "warn-name-shadowing",              Opt_WarnNameShadowing ),
1242   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns ),
1243   ( "warn-simple-patterns",             Opt_WarnSimplePatterns ),
1244   ( "warn-type-defaults",               Opt_WarnTypeDefaults ),
1245   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism ),
1246   ( "warn-unused-binds",                Opt_WarnUnusedBinds ),
1247   ( "warn-unused-imports",              Opt_WarnUnusedImports ),
1248   ( "warn-unused-matches",              Opt_WarnUnusedMatches ),
1249   ( "warn-deprecations",                Opt_WarnDeprecations ),
1250   ( "warn-orphans",                     Opt_WarnOrphans ),
1251   ( "warn-tabs",                        Opt_WarnTabs ),
1252   ( "print-explicit-foralls",           Opt_PrintExplicitForalls ),
1253   ( "strictness",                       Opt_Strictness ),
1254   ( "full-laziness",                    Opt_FullLaziness ),
1255   ( "liberate-case",                    Opt_LiberateCase ),
1256   ( "spec-constr",                      Opt_SpecConstr ),
1257   ( "cse",                              Opt_CSE ),
1258   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas ),
1259   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas ),
1260   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion ),
1261   ( "ignore-asserts",                   Opt_IgnoreAsserts ),
1262   ( "do-eta-reduction",                 Opt_DoEtaReduction ),
1263   ( "case-merge",                       Opt_CaseMerge ),
1264   ( "unbox-strict-fields",              Opt_UnboxStrictFields ),
1265   ( "dicts-cheap",                      Opt_DictsCheap ),
1266   ( "excess-precision",                 Opt_ExcessPrecision ),
1267   ( "asm-mangling",                     Opt_DoAsmMangling ),
1268   ( "print-bind-result",                Opt_PrintBindResult ),
1269   ( "force-recomp",                     Opt_ForceRecomp ),
1270   ( "hpc-no-auto",                      Opt_Hpc_No_Auto ),
1271   ( "rewrite-rules",                    Opt_RewriteRules ),
1272   ( "break-on-exception",               Opt_BreakOnException ),
1273   ( "break-on-error",                   Opt_BreakOnError ),
1274   ( "print-evld-with-show",             Opt_PrintEvldWithShow ),
1275   ( "print-bind-contents",              Opt_PrintBindContents ),
1276   ( "run-cps",                          Opt_RunCPSZ ),
1277   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack),
1278   ( "vectorise",                        Opt_Vectorise ),
1279   ( "regs-graph",                       Opt_RegsGraph),
1280   ( "regs-iterative",                   Opt_RegsIterative),
1281   -- Deprecated in favour of -XTemplateHaskell:
1282   ( "th",                               Opt_TemplateHaskell ),
1283   -- Deprecated in favour of -XForeignFunctionInterface:
1284   ( "fi",                               Opt_ForeignFunctionInterface ),
1285   -- Deprecated in favour of -XForeignFunctionInterface:
1286   ( "ffi",                              Opt_ForeignFunctionInterface ),
1287   -- Deprecated in favour of -XArrows:
1288   ( "arrows",                           Opt_Arrows ),
1289   -- Deprecated in favour of -XGenerics:
1290   ( "generics",                         Opt_Generics ),
1291   -- Deprecated in favour of -XImplicitPrelude:
1292   ( "implicit-prelude",                 Opt_ImplicitPrelude ),
1293   -- Deprecated in favour of -XBangPatterns:
1294   ( "bang-patterns",                    Opt_BangPatterns ),
1295   -- Deprecated in favour of -XMonomorphismRestriction:
1296   ( "monomorphism-restriction",         Opt_MonomorphismRestriction ),
1297   -- Deprecated in favour of -XMonoPatBinds:
1298   ( "mono-pat-binds",                   Opt_MonoPatBinds ),
1299   -- Deprecated in favour of -XExtendedDefaultRules:
1300   ( "extended-default-rules",           Opt_ExtendedDefaultRules ),
1301   -- Deprecated in favour of -XImplicitParams:
1302   ( "implicit-params",                  Opt_ImplicitParams ),
1303   -- Deprecated in favour of -XScopedTypeVariables:
1304   ( "scoped-type-variables",            Opt_ScopedTypeVariables ),
1305   -- Deprecated in favour of -XPArr:
1306   ( "parr",                             Opt_PArr ),
1307   -- Deprecated in favour of -XOverlappingInstances:
1308   ( "allow-overlapping-instances",      Opt_OverlappingInstances ),
1309   -- Deprecated in favour of -XUndecidableInstances:
1310   ( "allow-undecidable-instances",      Opt_UndecidableInstances ),
1311   -- Deprecated in favour of -XIncoherentInstances:
1312   ( "allow-incoherent-instances",       Opt_IncoherentInstances ),
1313   ( "gen-manifest",                     Opt_GenManifest ),
1314   ( "embed-manifest",                   Opt_EmbedManifest )
1315   ]
1316
1317 supportedLanguages :: [String]
1318 supportedLanguages = map fst xFlags
1319
1320 -- These -X<blah> flags can all be reversed with -XNo<blah>
1321 xFlags :: [(String, DynFlag)]
1322 xFlags = [
1323   ( "CPP",                              Opt_Cpp ),
1324   ( "PatternGuards",                    Opt_PatternGuards ),
1325   ( "UnicodeSyntax",                    Opt_UnicodeSyntax ),
1326   ( "MagicHash",                        Opt_MagicHash ),
1327   ( "PolymorphicComponents",            Opt_PolymorphicComponents ),
1328   ( "ExistentialQuantification",        Opt_ExistentialQuantification ),
1329   ( "KindSignatures",                   Opt_KindSignatures ),
1330   ( "PatternSignatures",                Opt_PatternSignatures ),
1331   ( "EmptyDataDecls",                   Opt_EmptyDataDecls ),
1332   ( "ParallelListComp",                 Opt_ParallelListComp ),
1333   ( "TransformListComp",                Opt_TransformListComp ),
1334   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface ),
1335   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes ),
1336   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms ),
1337   ( "Rank2Types",                       Opt_Rank2Types ),
1338   ( "RankNTypes",                       Opt_RankNTypes ),
1339   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes ),
1340   ( "TypeOperators",                    Opt_TypeOperators ),
1341   ( "RecursiveDo",                      Opt_RecursiveDo ),
1342   ( "Arrows",                           Opt_Arrows ),
1343   ( "PArr",                             Opt_PArr ),
1344   ( "TemplateHaskell",                  Opt_TemplateHaskell ),
1345   ( "QuasiQuotes",                      Opt_QuasiQuotes ),
1346   ( "Generics",                         Opt_Generics ),
1347   -- On by default:
1348   ( "ImplicitPrelude",                  Opt_ImplicitPrelude ),
1349   ( "RecordWildCards",                  Opt_RecordWildCards ),
1350   ( "RecordPuns",                       Opt_RecordPuns ),
1351   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields ),
1352   ( "OverloadedStrings",                Opt_OverloadedStrings ),
1353   ( "GADTs",                            Opt_GADTs ),
1354   ( "ViewPatterns",                     Opt_ViewPatterns),
1355   ( "TypeFamilies",                     Opt_TypeFamilies ),
1356   ( "BangPatterns",                     Opt_BangPatterns ),
1357   -- On by default:
1358   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction ),
1359   -- On by default (which is not strictly H98):
1360   ( "MonoPatBinds",                     Opt_MonoPatBinds ),
1361   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec),
1362   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules ),
1363   ( "ImplicitParams",                   Opt_ImplicitParams ),
1364   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables ),
1365   ( "UnboxedTuples",                    Opt_UnboxedTuples ),
1366   ( "StandaloneDeriving",               Opt_StandaloneDeriving ),
1367   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable ),
1368   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances ),
1369   ( "FlexibleContexts",                 Opt_FlexibleContexts ),
1370   ( "FlexibleInstances",                Opt_FlexibleInstances ),
1371   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods ),
1372   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses ),
1373   ( "FunctionalDependencies",           Opt_FunctionalDependencies ),
1374   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving ),
1375   ( "OverlappingInstances",             Opt_OverlappingInstances ),
1376   ( "UndecidableInstances",             Opt_UndecidableInstances ),
1377   ( "IncoherentInstances",              Opt_IncoherentInstances )
1378   ]
1379
1380 impliedFlags :: [(DynFlag, [DynFlag])]
1381 impliedFlags = [
1382    ( Opt_GADTs,               [Opt_RelaxedPolyRec] )    -- We want type-sig variables to 
1383                                                         --      be completely rigid for GADTs
1384  , ( Opt_ScopedTypeVariables, [Opt_RelaxedPolyRec] )    -- Ditto for scoped type variables; see
1385                                                         --      Note [Scoped tyvars] in TcBinds
1386   ]
1387
1388 glasgowExtsFlags :: [DynFlag]
1389 glasgowExtsFlags = [
1390              Opt_PrintExplicitForalls
1391            , Opt_ForeignFunctionInterface
1392            , Opt_UnliftedFFITypes
1393            , Opt_GADTs
1394            , Opt_ImplicitParams 
1395            , Opt_ScopedTypeVariables
1396            , Opt_UnboxedTuples
1397            , Opt_TypeSynonymInstances
1398            , Opt_StandaloneDeriving
1399            , Opt_DeriveDataTypeable
1400            , Opt_FlexibleContexts
1401            , Opt_FlexibleInstances
1402            , Opt_ConstrainedClassMethods
1403            , Opt_MultiParamTypeClasses
1404            , Opt_FunctionalDependencies
1405            , Opt_MagicHash
1406            , Opt_PolymorphicComponents
1407            , Opt_ExistentialQuantification
1408            , Opt_UnicodeSyntax
1409            , Opt_PatternGuards
1410            , Opt_LiberalTypeSynonyms
1411            , Opt_RankNTypes
1412            , Opt_ImpredicativeTypes
1413            , Opt_TypeOperators
1414            , Opt_RecursiveDo
1415            , Opt_ParallelListComp
1416            , Opt_EmptyDataDecls
1417            , Opt_KindSignatures
1418            , Opt_PatternSignatures
1419            , Opt_GeneralizedNewtypeDeriving
1420            , Opt_TypeFamilies ]
1421
1422 ------------------
1423 isFlag :: [(String,a)] -> String -> Bool
1424 isFlag flags f = any (\(ff,_) -> ff == f) flags
1425
1426 isPrefFlag :: String -> [(String,a)] -> String -> Bool
1427 isPrefFlag pref flags no_f
1428   | Just f <- maybePrefixMatch pref no_f = isFlag flags f
1429   | otherwise                            = False
1430
1431 ------------------
1432 getFlag :: [(String,a)] -> String -> a
1433 getFlag flags f = case [ opt | (ff, opt) <- flags, ff == f] of
1434                       (o:_)  -> o
1435                       []     -> panic ("get_flag " ++ f)
1436
1437 getPrefFlag :: String -> [(String,a)] -> String -> a
1438 getPrefFlag pref flags f = getFlag flags (fromJust (maybePrefixMatch pref f))
1439 -- We should only be passed flags which match the prefix
1440
1441 -- -----------------------------------------------------------------------------
1442 -- Parsing the dynamic flags.
1443
1444 parseDynamicFlags :: DynFlags -> [String] -> IO (DynFlags,[String])
1445 parseDynamicFlags dflags args = do
1446   let ((leftover,errs),dflags') 
1447           = runCmdLine (processArgs dynamic_flags args) dflags
1448   when (not (null errs)) $ do
1449     throwDyn (UsageError (unlines errs))
1450   return (dflags', leftover)
1451
1452
1453 type DynP = CmdLineP DynFlags
1454
1455 upd :: (DynFlags -> DynFlags) -> DynP ()
1456 upd f = do 
1457    dfs <- getCmdLineState
1458    putCmdLineState $! (f dfs)
1459
1460 --------------------------
1461 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1462 setDynFlag f = upd (\dfs -> foldl dopt_set (dopt_set dfs f) deps)
1463   where
1464     deps = [ d | (f', ds) <- impliedFlags, f' == f, d <- ds ]
1465         -- When you set f, set the ones it implies
1466         -- When you un-set f, however, we don't un-set the things it implies
1467         --      (except for -fno-glasgow-exts, which is treated specially)
1468
1469 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1470
1471 --------------------------
1472 setDumpFlag :: DynFlag -> OptKind DynP
1473 setDumpFlag dump_flag 
1474   = NoArg (setDynFlag Opt_ForceRecomp >> setDynFlag dump_flag)
1475         -- Whenver we -ddump, switch off the recompilation checker,
1476         -- else you don't see the dump!
1477
1478 setVerboseCore2Core :: DynP ()
1479 setVerboseCore2Core = do setDynFlag Opt_ForceRecomp
1480                          setDynFlag Opt_D_verbose_core2core
1481                          upd (\s -> s { shouldDumpSimplPhase = const True })
1482
1483 setDumpSimplPhases :: String -> DynP ()
1484 setDumpSimplPhases s = do setDynFlag Opt_ForceRecomp
1485                           upd (\s -> s { shouldDumpSimplPhase = spec })
1486   where
1487     spec :: SimplifierMode -> Bool
1488     spec = join (||)
1489          . map (join (&&) . map match . split ':')
1490          . split ','
1491          $ case s of
1492              '=' : s' -> s'
1493              _        -> s
1494
1495     join :: (Bool -> Bool -> Bool)
1496          -> [SimplifierMode -> Bool]
1497          -> SimplifierMode -> Bool
1498     join _  [] = const True
1499     join op ss = foldr1 (\f g x -> f x `op` g x) ss
1500
1501     match :: String -> SimplifierMode -> Bool
1502     match "" = const True
1503     match s  = case reads s of
1504                 [(n,"")] -> phase_num  n
1505                 _        -> phase_name s
1506
1507     phase_num :: Int -> SimplifierMode -> Bool
1508     phase_num n (SimplPhase k _) = n == k
1509     phase_num _ _                = False
1510
1511     phase_name :: String -> SimplifierMode -> Bool
1512     phase_name s SimplGently       = s == "gentle"
1513     phase_name s (SimplPhase _ ss) = s `elem` ss
1514
1515 setVerbosity :: Maybe Int -> DynP ()
1516 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1517
1518 addCmdlineHCInclude :: String -> DynP ()
1519 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1520
1521 extraPkgConf_ :: FilePath -> DynP ()
1522 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
1523
1524 exposePackage, hidePackage, ignorePackage :: String -> DynP ()
1525 exposePackage p = 
1526   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
1527 hidePackage p = 
1528   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
1529 ignorePackage p = 
1530   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
1531
1532 setPackageName :: String -> DynFlags -> DynFlags
1533 setPackageName p
1534   | Nothing <- unpackPackageId pid
1535   = throwDyn (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
1536   | otherwise
1537   = \s -> s{ thisPackage = pid }
1538   where
1539         pid = stringToPackageId p
1540
1541 -- If we're linking a binary, then only targets that produce object
1542 -- code are allowed (requests for other target types are ignored).
1543 setTarget :: HscTarget -> DynP ()
1544 setTarget l = upd set
1545   where 
1546    set dfs 
1547      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
1548      | otherwise = dfs
1549
1550 -- Changes the target only if we're compiling object code.  This is
1551 -- used by -fasm and -fvia-C, which switch from one to the other, but
1552 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
1553 -- can be safely used in an OPTIONS_GHC pragma.
1554 setObjTarget :: HscTarget -> DynP ()
1555 setObjTarget l = upd set
1556   where 
1557    set dfs 
1558      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
1559      | otherwise = dfs
1560
1561 setOptLevel :: Int -> DynFlags -> DynFlags
1562 setOptLevel n dflags
1563    | hscTarget dflags == HscInterpreted && n > 0
1564         = dflags
1565             -- not in IO any more, oh well:
1566             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
1567    | otherwise
1568         = updOptLevel n dflags
1569
1570
1571 setMainIs :: String -> DynP ()
1572 setMainIs arg
1573   | not (null main_fn) && isLower (head main_fn)
1574      -- The arg looked like "Foo.Bar.baz"
1575   = upd $ \d -> d{ mainFunIs = Just main_fn,
1576                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
1577
1578   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
1579   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
1580   
1581   | otherwise                   -- The arg looked like "baz"
1582   = upd $ \d -> d{ mainFunIs = Just arg }
1583   where
1584     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
1585
1586 -----------------------------------------------------------------------------
1587 -- Paths & Libraries
1588
1589 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
1590
1591 -- -i on its own deletes the import paths
1592 addImportPath "" = upd (\s -> s{importPaths = []})
1593 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
1594
1595
1596 addLibraryPath p = 
1597   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
1598
1599 addIncludePath p = 
1600   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
1601
1602 addFrameworkPath p = 
1603   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
1604
1605 #ifndef mingw32_TARGET_OS
1606 split_marker :: Char
1607 split_marker = ':'   -- not configurable (ToDo)
1608 #endif
1609
1610 splitPathList :: String -> [String]
1611 splitPathList s = filter notNull (splitUp s)
1612                 -- empty paths are ignored: there might be a trailing
1613                 -- ':' in the initial list, for example.  Empty paths can
1614                 -- cause confusion when they are translated into -I options
1615                 -- for passing to gcc.
1616   where
1617 #ifndef mingw32_TARGET_OS
1618     splitUp xs = split split_marker xs
1619 #else 
1620      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
1621      -- 
1622      -- That is, if "foo:bar:baz" is used, this interpreted as
1623      -- consisting of three entries, 'foo', 'bar', 'baz'.
1624      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
1625      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
1626      --
1627      -- Notice that no attempt is made to fully replace the 'standard'
1628      -- split marker ':' with the Windows / DOS one, ';'. The reason being
1629      -- that this will cause too much breakage for users & ':' will
1630      -- work fine even with DOS paths, if you're not insisting on being silly.
1631      -- So, use either.
1632     splitUp []             = []
1633     splitUp (x:':':div:xs) | div `elem` dir_markers
1634                            = ((x:':':div:p): splitUp rs)
1635                            where
1636                               (p,rs) = findNextPath xs
1637           -- we used to check for existence of the path here, but that
1638           -- required the IO monad to be threaded through the command-line
1639           -- parser which is quite inconvenient.  The 
1640     splitUp xs = cons p (splitUp rs)
1641                where
1642                  (p,rs) = findNextPath xs
1643     
1644                  cons "" xs = xs
1645                  cons x  xs = x:xs
1646
1647     -- will be called either when we've consumed nought or the
1648     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
1649     -- finding the next split marker.
1650     findNextPath xs = 
1651         case break (`elem` split_markers) xs of
1652            (p, _:ds) -> (p, ds)
1653            (p, xs)   -> (p, xs)
1654
1655     split_markers :: [Char]
1656     split_markers = [':', ';']
1657
1658     dir_markers :: [Char]
1659     dir_markers = ['/', '\\']
1660 #endif
1661
1662 -- -----------------------------------------------------------------------------
1663 -- tmpDir, where we store temporary files.
1664
1665 setTmpDir :: FilePath -> DynFlags -> DynFlags
1666 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
1667   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
1668   -- seem necessary now --SDM 7/2/2008
1669
1670 -----------------------------------------------------------------------------
1671 -- Hpc stuff
1672
1673 setOptHpcDir :: String -> DynP ()
1674 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
1675
1676 -----------------------------------------------------------------------------
1677 -- Via-C compilation stuff
1678
1679 -- There are some options that we need to pass to gcc when compiling
1680 -- Haskell code via C, but are only supported by recent versions of
1681 -- gcc.  The configure script decides which of these options we need,
1682 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
1683 -- read before each via-C compilation.  The advantage of having these
1684 -- in a separate file is that the file can be created at install-time
1685 -- depending on the available gcc version, and even re-generated  later
1686 -- if gcc is upgraded.
1687 --
1688 -- The options below are not dependent on the version of gcc, only the
1689 -- platform.
1690
1691 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
1692                               [String]) -- for registerised HC compilations
1693 machdepCCOpts _dflags
1694 #if alpha_TARGET_ARCH
1695         =       ( ["-w", "-mieee"
1696 #ifdef HAVE_THREADED_RTS_SUPPORT
1697                     , "-D_REENTRANT"
1698 #endif
1699                    ], [] )
1700         -- For now, to suppress the gcc warning "call-clobbered
1701         -- register used for global register variable", we simply
1702         -- disable all warnings altogether using the -w flag. Oh well.
1703
1704 #elif hppa_TARGET_ARCH
1705         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
1706         -- (very nice, but too bad the HP /usr/include files don't agree.)
1707         = ( ["-D_HPUX_SOURCE"], [] )
1708
1709 #elif m68k_TARGET_ARCH
1710       -- -fno-defer-pop : for the .hc files, we want all the pushing/
1711       --    popping of args to routines to be explicit; if we let things
1712       --    be deferred 'til after an STGJUMP, imminent death is certain!
1713       --
1714       -- -fomit-frame-pointer : *don't*
1715       --     It's better to have a6 completely tied up being a frame pointer
1716       --     rather than let GCC pick random things to do with it.
1717       --     (If we want to steal a6, then we would try to do things
1718       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
1719         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
1720
1721 #elif i386_TARGET_ARCH
1722       -- -fno-defer-pop : basically the same game as for m68k
1723       --
1724       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
1725       --   the fp (%ebp) for our register maps.
1726         =  let n_regs = stolen_x86_regs _dflags
1727                sta = opt_Static
1728            in
1729                     ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
1730 --                    , if "mingw32" `isSuffixOf` cTARGETPLATFORM then "-mno-cygwin" else "" 
1731                       ],
1732                       [ "-fno-defer-pop",
1733                         "-fomit-frame-pointer",
1734                         -- we want -fno-builtin, because when gcc inlines
1735                         -- built-in functions like memcpy() it tends to
1736                         -- run out of registers, requiring -monly-n-regs
1737                         "-fno-builtin",
1738                         "-DSTOLEN_X86_REGS="++show n_regs ]
1739                     )
1740
1741 #elif ia64_TARGET_ARCH
1742         = ( [], ["-fomit-frame-pointer", "-G0"] )
1743
1744 #elif x86_64_TARGET_ARCH
1745         = ( [], ["-fomit-frame-pointer",
1746                  "-fno-asynchronous-unwind-tables",
1747                         -- the unwind tables are unnecessary for HC code,
1748                         -- and get in the way of -split-objs.  Another option
1749                         -- would be to throw them away in the mangler, but this
1750                         -- is easier.
1751                  "-fno-builtin"
1752                         -- calling builtins like strlen() using the FFI can
1753                         -- cause gcc to run out of regs, so use the external
1754                         -- version.
1755                 ] )
1756
1757 #elif sparc_TARGET_ARCH
1758         = ( [], ["-w"] )
1759         -- For now, to suppress the gcc warning "call-clobbered
1760         -- register used for global register variable", we simply
1761         -- disable all warnings altogether using the -w flag. Oh well.
1762
1763 #elif powerpc_apple_darwin_TARGET
1764       -- -no-cpp-precomp:
1765       --     Disable Apple's precompiling preprocessor. It's a great thing
1766       --     for "normal" programs, but it doesn't support register variable
1767       --     declarations.
1768         = ( [], ["-no-cpp-precomp"] )
1769 #else
1770         = ( [], [] )
1771 #endif
1772
1773 picCCOpts :: DynFlags -> [String]
1774 picCCOpts _dflags
1775 #if darwin_TARGET_OS
1776       -- Apple prefers to do things the other way round.
1777       -- PIC is on by default.
1778       -- -mdynamic-no-pic:
1779       --     Turn off PIC code generation.
1780       -- -fno-common:
1781       --     Don't generate "common" symbols - these are unwanted
1782       --     in dynamic libraries.
1783
1784     | opt_PIC
1785         = ["-fno-common", "-D__PIC__"]
1786     | otherwise
1787         = ["-mdynamic-no-pic"]
1788 #elif mingw32_TARGET_OS
1789       -- no -fPIC for Windows
1790     | opt_PIC
1791         = ["-D__PIC__"]
1792     | otherwise
1793         = []
1794 #else
1795     | opt_PIC
1796         = ["-fPIC", "-D__PIC__"]
1797     | otherwise
1798         = []
1799 #endif
1800
1801 -- -----------------------------------------------------------------------------
1802 -- Splitting
1803
1804 can_split :: Bool
1805 can_split = cSplitObjs == "YES"
1806
1807 -- -----------------------------------------------------------------------------
1808 -- Compiler Info
1809
1810 compilerInfo :: [(String, String)]
1811 compilerInfo = [("Project name",                cProjectName),
1812                 ("Project version",             cProjectVersion),
1813                 ("Booter version",              cBooterVersion),
1814                 ("Stage",                       cStage),
1815                 ("Interface file version",      cHscIfaceFileVersion),
1816                 ("Have interpreter",            cGhcWithInterpreter),
1817                 ("Object splitting",            cSplitObjs),
1818                 ("Have native code generator",  cGhcWithNativeCodeGen),
1819                 ("Support SMP",                 cGhcWithSMP),
1820                 ("Unregisterised",              cGhcUnregisterised),
1821                 ("Tables next to code",         cGhcEnableTablesNextToCode),
1822                 ("Win32 DLLs",                  cEnableWin32DLLs),
1823                 ("RTS ways",                    cGhcRTSWays),
1824                 ("Leading underscore",          cLeadingUnderscore)]
1825