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