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