Another round of External Core fixes
[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_CSE
241    | Opt_LiberateCase
242    | Opt_SpecConstr
243    | Opt_IgnoreInterfacePragmas
244    | Opt_OmitInterfacePragmas
245    | Opt_DoLambdaEtaExpansion
246    | Opt_IgnoreAsserts
247    | Opt_DoEtaReduction
248    | Opt_CaseMerge
249    | Opt_UnboxStrictFields
250    | Opt_DictsCheap
251    | Opt_RewriteRules
252    | Opt_Vectorise
253    | Opt_RegsGraph                      -- do graph coloring register allocation
254    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
255
256    -- misc opts
257    | Opt_Cpp
258    | Opt_Pp
259    | Opt_ForceRecomp
260    | Opt_DryRun
261    | Opt_DoAsmMangling
262    | Opt_ExcessPrecision
263    | Opt_ReadUserPackageConf
264    | Opt_NoHsMain
265    | Opt_SplitObjs
266    | Opt_StgStats
267    | Opt_HideAllPackages
268    | Opt_PrintBindResult
269    | Opt_Haddock
270    | Opt_HaddockOptions
271    | Opt_Hpc_No_Auto
272    | Opt_BreakOnException
273    | Opt_BreakOnError
274    | Opt_PrintEvldWithShow
275    | Opt_PrintBindContents
276    | Opt_GenManifest
277    | Opt_EmbedManifest
278    | Opt_RunCPSZ
279    | Opt_ConvertToZipCfgAndBack
280
281    -- keeping stuff
282    | Opt_KeepHiDiffs
283    | Opt_KeepHcFiles
284    | Opt_KeepSFiles
285    | Opt_KeepRawSFiles
286    | Opt_KeepTmpFiles
287
288    deriving (Eq, Show)
289  
290 data DynFlags = DynFlags {
291   ghcMode               :: GhcMode,
292   ghcLink               :: GhcLink,
293   coreToDo              :: Maybe [CoreToDo], -- reserved for -Ofile
294   stgToDo               :: Maybe [StgToDo],  -- similarly
295   hscTarget             :: HscTarget,
296   hscOutName            :: String,      -- name of the output file
297   extCoreName           :: String,      -- name of the .core output file
298   verbosity             :: Int,         -- verbosity level
299   optLevel              :: Int,         -- optimisation level
300   simplPhases           :: Int,         -- number of simplifier phases
301   maxSimplIterations    :: Int,         -- max simplifier iterations
302   shouldDumpSimplPhase  :: SimplifierMode -> Bool,
303   ruleCheck             :: Maybe String,
304
305   specConstrThreshold   :: Maybe Int,   -- Threshold for SpecConstr
306   specConstrCount       :: Maybe Int,   -- Max number of specialisations for any one function
307   liberateCaseThreshold :: Maybe Int,   -- Threshold for LiberateCase 
308
309   stolen_x86_regs       :: Int,         
310   cmdlineHcIncludes     :: [String],    -- -#includes
311   importPaths           :: [FilePath],
312   mainModIs             :: Module,
313   mainFunIs             :: Maybe String,
314   ctxtStkDepth          :: Int,         -- Typechecker context stack depth
315
316   thisPackage           :: PackageId,
317
318   -- ways
319   wayNames              :: [WayName],   -- way flags from the cmd line
320   buildTag              :: String,      -- the global "way" (eg. "p" for prof)
321   rtsBuildTag           :: String,      -- the RTS "way"
322   
323   -- paths etc.
324   objectDir             :: Maybe String,
325   hiDir                 :: Maybe String,
326   stubDir               :: Maybe String,
327
328   objectSuf             :: String,
329   hcSuf                 :: String,
330   hiSuf                 :: String,
331
332   outputFile            :: Maybe String,
333   outputHi              :: Maybe String,
334   dynLibLoader          :: DynLibLoader,
335
336   -- | This is set by DriverPipeline.runPipeline based on where
337   --    its output is going.
338   dumpPrefix            :: Maybe FilePath,
339
340   -- | Override the dumpPrefix set by runPipeline.
341   --    Set by -ddump-file-prefix
342   dumpPrefixForce       :: Maybe FilePath,
343
344   includePaths          :: [String],
345   libraryPaths          :: [String],
346   frameworkPaths        :: [String],    -- used on darwin only
347   cmdlineFrameworks     :: [String],    -- ditto
348   tmpDir                :: String,      -- no trailing '/'
349   
350   ghcUsagePath          :: FilePath,    -- Filled in by SysTools
351   ghciUsagePath         :: FilePath,    -- ditto
352
353   hpcDir                :: String,      -- ^ path to store the .mix files
354
355   -- options for particular phases
356   opt_L                 :: [String],
357   opt_P                 :: [String],
358   opt_F                 :: [String],
359   opt_c                 :: [String],
360   opt_m                 :: [String],
361   opt_a                 :: [String],
362   opt_l                 :: [String],
363   opt_dep               :: [String],
364   opt_windres           :: [String],
365
366   -- commands for particular phases
367   pgm_L                 :: String,
368   pgm_P                 :: (String,[Option]),
369   pgm_F                 :: String,
370   pgm_c                 :: (String,[Option]),
371   pgm_m                 :: (String,[Option]),
372   pgm_s                 :: (String,[Option]),
373   pgm_a                 :: (String,[Option]),
374   pgm_l                 :: (String,[Option]),
375   pgm_dll               :: (String,[Option]),
376   pgm_T                 :: String,
377   pgm_sysman            :: String,
378   pgm_windres           :: String,
379
380   --  Package flags
381   extraPkgConfs         :: [FilePath],
382   topDir                :: FilePath,    -- filled in by SysTools
383   systemPackageConfig   :: FilePath,    -- ditto
384         -- The -package-conf flags given on the command line, in the order
385         -- they appeared.
386
387   packageFlags          :: [PackageFlag],
388         -- The -package and -hide-package flags from the command-line
389
390   -- Package state
391   -- NB. do not modify this field, it is calculated by 
392   -- Packages.initPackages and Packages.updatePackages.
393   pkgDatabase           :: Maybe (UniqFM PackageConfig),
394   pkgState              :: PackageState,
395
396   -- hsc dynamic flags
397   flags                 :: [DynFlag],
398   
399   -- message output
400   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
401
402   haddockOptions :: Maybe String
403  }
404
405 data HscTarget
406   = HscC
407   | HscAsm
408   | HscJava
409   | HscInterpreted
410   | HscNothing
411   deriving (Eq, Show)
412
413 -- | will this target result in an object file on the disk?
414 isObjectTarget :: HscTarget -> Bool
415 isObjectTarget HscC     = True
416 isObjectTarget HscAsm   = True
417 isObjectTarget _        = False
418
419 -- | The 'GhcMode' tells us whether we're doing multi-module
420 -- compilation (controlled via the "GHC" API) or one-shot
421 -- (single-module) compilation.  This makes a difference primarily to
422 -- the "Finder": in one-shot mode we look for interface files for
423 -- imported modules, but in multi-module mode we look for source files
424 -- in order to check whether they need to be recompiled.
425 data GhcMode
426   = CompManager         -- ^ --make, GHCi, etc.
427   | OneShot             -- ^ ghc -c Foo.hs
428   | MkDepend            -- ^ ghc -M, see Finder for why we need this
429   deriving Eq
430
431 isOneShot :: GhcMode -> Bool
432 isOneShot OneShot = True
433 isOneShot _other  = False
434
435 -- | What kind of linking to do.
436 data GhcLink    -- What to do in the link step, if there is one
437   = NoLink              -- Don't link at all
438   | LinkBinary          -- Link object code into a binary
439   | LinkInMemory        -- Use the in-memory dynamic linker
440   | LinkDynLib          -- Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
441   deriving (Eq, Show)
442
443 isNoLink :: GhcLink -> Bool
444 isNoLink NoLink = True
445 isNoLink _      = False
446
447 data PackageFlag
448   = ExposePackage  String
449   | HidePackage    String
450   | IgnorePackage  String
451   deriving Eq
452
453 defaultHscTarget :: HscTarget
454 defaultHscTarget = defaultObjectTarget
455
456 -- | the 'HscTarget' value corresponding to the default way to create
457 -- object files on the current platform.
458 defaultObjectTarget :: HscTarget
459 defaultObjectTarget
460   | cGhcWithNativeCodeGen == "YES"      =  HscAsm
461   | otherwise                           =  HscC
462
463 data DynLibLoader
464   = Deployable
465   | Wrapped (Maybe String)
466   | SystemDependent
467   deriving Eq
468
469 initDynFlags :: DynFlags -> IO DynFlags
470 initDynFlags dflags = do
471  -- someday these will be dynamic flags
472  ways <- readIORef v_Ways
473  build_tag <- readIORef v_Build_tag
474  rts_build_tag <- readIORef v_RTS_Build_tag
475  return dflags{
476         wayNames        = ways,
477         buildTag        = build_tag,
478         rtsBuildTag     = rts_build_tag
479         }
480
481 defaultDynFlags :: DynFlags
482 defaultDynFlags =
483      DynFlags {
484         ghcMode                 = CompManager,
485         ghcLink                 = LinkBinary,
486         coreToDo                = Nothing,
487         stgToDo                 = Nothing, 
488         hscTarget               = defaultHscTarget, 
489         hscOutName              = "", 
490         extCoreName             = "",
491         verbosity               = 0, 
492         optLevel                = 0,
493         simplPhases             = 2,
494         maxSimplIterations      = 4,
495         shouldDumpSimplPhase    = const False,
496         ruleCheck               = Nothing,
497         specConstrThreshold     = Just 200,
498         specConstrCount         = Just 3,
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   ,  ( "fspec-constr-count",          IntSuffix (\n ->
1189                 upd (\dfs -> dfs{ specConstrCount = Just n })))
1190   ,  ( "fno-spec-constr-count",   NoArg (
1191                 upd (\dfs -> dfs{ specConstrCount = Nothing })))
1192   ,  ( "fliberate-case-threshold",    IntSuffix (\n ->
1193                 upd (\dfs -> dfs{ liberateCaseThreshold = Just n })))
1194   ,  ( "fno-liberate-case-threshold", NoArg (
1195                 upd (\dfs -> dfs{ liberateCaseThreshold = Nothing })))
1196
1197   ,  ( "frule-check",     SepArg (\s -> upd (\dfs -> dfs{ ruleCheck = Just s })))
1198   ,  ( "fcontext-stack" , IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
1199
1200         ------ Compiler flags -----------------------------------------------
1201
1202   ,  ( "fasm",             NoArg (setObjTarget HscAsm) )
1203   ,  ( "fvia-c",           NoArg (setObjTarget HscC) )
1204   ,  ( "fvia-C",           NoArg (setObjTarget HscC) )
1205
1206   ,  ( "fno-code",         NoArg (setTarget HscNothing))
1207   ,  ( "fbyte-code",       NoArg (setTarget HscInterpreted) )
1208   ,  ( "fobject-code",     NoArg (setTarget defaultHscTarget) )
1209
1210   ,  ( "fglasgow-exts",    NoArg (mapM_ setDynFlag   glasgowExtsFlags) )
1211   ,  ( "fno-glasgow-exts", NoArg (mapM_ unSetDynFlag glasgowExtsFlags) )
1212
1213      -- the rest of the -f* and -fno-* flags
1214   ,  ( "f",                PrefixPred (isFlag   fFlags)
1215                            (\f -> setDynFlag   (getFlag   fFlags f)) )
1216   ,  ( "f",                PrefixPred (isPrefFlag "no-" fFlags)
1217                            (\f -> unSetDynFlag (getPrefFlag "no-" fFlags f)) )
1218
1219      -- the -X* and -XNo* flags
1220   ,  ( "X",                PrefixPred (isFlag   xFlags)
1221                            (\f -> setDynFlag   (getFlag   xFlags f)) )
1222   ,  ( "X",                PrefixPred (isPrefFlag "No" xFlags)
1223                            (\f -> unSetDynFlag (getPrefFlag "No" xFlags f)) )
1224  ]
1225
1226 -- these -f<blah> flags can all be reversed with -fno-<blah>
1227
1228 fFlags :: [(String, DynFlag)]
1229 fFlags = [
1230   ( "warn-dodgy-imports",               Opt_WarnDodgyImports ),
1231   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports ),
1232   ( "warn-hi-shadowing",                Opt_WarnHiShadows ),
1233   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude ),
1234   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns ),
1235   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd ),
1236   ( "warn-missing-fields",              Opt_WarnMissingFields ),
1237   ( "warn-missing-methods",             Opt_WarnMissingMethods ),
1238   ( "warn-missing-signatures",          Opt_WarnMissingSigs ),
1239   ( "warn-name-shadowing",              Opt_WarnNameShadowing ),
1240   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns ),
1241   ( "warn-simple-patterns",             Opt_WarnSimplePatterns ),
1242   ( "warn-type-defaults",               Opt_WarnTypeDefaults ),
1243   ( "warn-monomorphism-restriction",    Opt_WarnMonomorphism ),
1244   ( "warn-unused-binds",                Opt_WarnUnusedBinds ),
1245   ( "warn-unused-imports",              Opt_WarnUnusedImports ),
1246   ( "warn-unused-matches",              Opt_WarnUnusedMatches ),
1247   ( "warn-deprecations",                Opt_WarnDeprecations ),
1248   ( "warn-orphans",                     Opt_WarnOrphans ),
1249   ( "warn-tabs",                        Opt_WarnTabs ),
1250   ( "print-explicit-foralls",           Opt_PrintExplicitForalls ),
1251   ( "strictness",                       Opt_Strictness ),
1252   ( "full-laziness",                    Opt_FullLaziness ),
1253   ( "liberate-case",                    Opt_LiberateCase ),
1254   ( "spec-constr",                      Opt_SpecConstr ),
1255   ( "cse",                              Opt_CSE ),
1256   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas ),
1257   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas ),
1258   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion ),
1259   ( "ignore-asserts",                   Opt_IgnoreAsserts ),
1260   ( "do-eta-reduction",                 Opt_DoEtaReduction ),
1261   ( "case-merge",                       Opt_CaseMerge ),
1262   ( "unbox-strict-fields",              Opt_UnboxStrictFields ),
1263   ( "dicts-cheap",                      Opt_DictsCheap ),
1264   ( "excess-precision",                 Opt_ExcessPrecision ),
1265   ( "asm-mangling",                     Opt_DoAsmMangling ),
1266   ( "print-bind-result",                Opt_PrintBindResult ),
1267   ( "force-recomp",                     Opt_ForceRecomp ),
1268   ( "hpc-no-auto",                      Opt_Hpc_No_Auto ),
1269   ( "rewrite-rules",                    Opt_RewriteRules ),
1270   ( "break-on-exception",               Opt_BreakOnException ),
1271   ( "break-on-error",                   Opt_BreakOnError ),
1272   ( "print-evld-with-show",             Opt_PrintEvldWithShow ),
1273   ( "print-bind-contents",              Opt_PrintBindContents ),
1274   ( "run-cps",                          Opt_RunCPSZ ),
1275   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack),
1276   ( "vectorise",                        Opt_Vectorise ),
1277   ( "regs-graph",                       Opt_RegsGraph),
1278   ( "regs-iterative",                   Opt_RegsIterative),
1279   -- Deprecated in favour of -XTemplateHaskell:
1280   ( "th",                               Opt_TemplateHaskell ),
1281   -- Deprecated in favour of -XForeignFunctionInterface:
1282   ( "fi",                               Opt_ForeignFunctionInterface ),
1283   -- Deprecated in favour of -XForeignFunctionInterface:
1284   ( "ffi",                              Opt_ForeignFunctionInterface ),
1285   -- Deprecated in favour of -XArrows:
1286   ( "arrows",                           Opt_Arrows ),
1287   -- Deprecated in favour of -XGenerics:
1288   ( "generics",                         Opt_Generics ),
1289   -- Deprecated in favour of -XImplicitPrelude:
1290   ( "implicit-prelude",                 Opt_ImplicitPrelude ),
1291   -- Deprecated in favour of -XBangPatterns:
1292   ( "bang-patterns",                    Opt_BangPatterns ),
1293   -- Deprecated in favour of -XMonomorphismRestriction:
1294   ( "monomorphism-restriction",         Opt_MonomorphismRestriction ),
1295   -- Deprecated in favour of -XMonoPatBinds:
1296   ( "mono-pat-binds",                   Opt_MonoPatBinds ),
1297   -- Deprecated in favour of -XExtendedDefaultRules:
1298   ( "extended-default-rules",           Opt_ExtendedDefaultRules ),
1299   -- Deprecated in favour of -XImplicitParams:
1300   ( "implicit-params",                  Opt_ImplicitParams ),
1301   -- Deprecated in favour of -XScopedTypeVariables:
1302   ( "scoped-type-variables",            Opt_ScopedTypeVariables ),
1303   -- Deprecated in favour of -XPArr:
1304   ( "parr",                             Opt_PArr ),
1305   -- Deprecated in favour of -XOverlappingInstances:
1306   ( "allow-overlapping-instances",      Opt_OverlappingInstances ),
1307   -- Deprecated in favour of -XUndecidableInstances:
1308   ( "allow-undecidable-instances",      Opt_UndecidableInstances ),
1309   -- Deprecated in favour of -XIncoherentInstances:
1310   ( "allow-incoherent-instances",       Opt_IncoherentInstances ),
1311   ( "gen-manifest",                     Opt_GenManifest ),
1312   ( "embed-manifest",                   Opt_EmbedManifest )
1313   ]
1314
1315 supportedLanguages :: [String]
1316 supportedLanguages = map fst xFlags
1317
1318 -- These -X<blah> flags can all be reversed with -XNo<blah>
1319 xFlags :: [(String, DynFlag)]
1320 xFlags = [
1321   ( "CPP",                              Opt_Cpp ),
1322   ( "PatternGuards",                    Opt_PatternGuards ),
1323   ( "UnicodeSyntax",                    Opt_UnicodeSyntax ),
1324   ( "MagicHash",                        Opt_MagicHash ),
1325   ( "PolymorphicComponents",            Opt_PolymorphicComponents ),
1326   ( "ExistentialQuantification",        Opt_ExistentialQuantification ),
1327   ( "KindSignatures",                   Opt_KindSignatures ),
1328   ( "PatternSignatures",                Opt_PatternSignatures ),
1329   ( "EmptyDataDecls",                   Opt_EmptyDataDecls ),
1330   ( "ParallelListComp",                 Opt_ParallelListComp ),
1331   ( "TransformListComp",                Opt_TransformListComp ),
1332   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface ),
1333   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes ),
1334   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms ),
1335   ( "Rank2Types",                       Opt_Rank2Types ),
1336   ( "RankNTypes",                       Opt_RankNTypes ),
1337   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes ),
1338   ( "TypeOperators",                    Opt_TypeOperators ),
1339   ( "RecursiveDo",                      Opt_RecursiveDo ),
1340   ( "Arrows",                           Opt_Arrows ),
1341   ( "PArr",                             Opt_PArr ),
1342   ( "TemplateHaskell",                  Opt_TemplateHaskell ),
1343   ( "QuasiQuotes",                      Opt_QuasiQuotes ),
1344   ( "Generics",                         Opt_Generics ),
1345   -- On by default:
1346   ( "ImplicitPrelude",                  Opt_ImplicitPrelude ),
1347   ( "RecordWildCards",                  Opt_RecordWildCards ),
1348   ( "RecordPuns",                       Opt_RecordPuns ),
1349   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields ),
1350   ( "OverloadedStrings",                Opt_OverloadedStrings ),
1351   ( "GADTs",                            Opt_GADTs ),
1352   ( "ViewPatterns",                     Opt_ViewPatterns),
1353   ( "TypeFamilies",                     Opt_TypeFamilies ),
1354   ( "BangPatterns",                     Opt_BangPatterns ),
1355   -- On by default:
1356   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction ),
1357   -- On by default (which is not strictly H98):
1358   ( "MonoPatBinds",                     Opt_MonoPatBinds ),
1359   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec),
1360   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules ),
1361   ( "ImplicitParams",                   Opt_ImplicitParams ),
1362   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables ),
1363   ( "UnboxedTuples",                    Opt_UnboxedTuples ),
1364   ( "StandaloneDeriving",               Opt_StandaloneDeriving ),
1365   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable ),
1366   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances ),
1367   ( "FlexibleContexts",                 Opt_FlexibleContexts ),
1368   ( "FlexibleInstances",                Opt_FlexibleInstances ),
1369   ( "ConstrainedClassMethods",          Opt_ConstrainedClassMethods ),
1370   ( "MultiParamTypeClasses",            Opt_MultiParamTypeClasses ),
1371   ( "FunctionalDependencies",           Opt_FunctionalDependencies ),
1372   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving ),
1373   ( "OverlappingInstances",             Opt_OverlappingInstances ),
1374   ( "UndecidableInstances",             Opt_UndecidableInstances ),
1375   ( "IncoherentInstances",              Opt_IncoherentInstances )
1376   ]
1377
1378 impliedFlags :: [(DynFlag, [DynFlag])]
1379 impliedFlags = [
1380    ( Opt_GADTs,               [Opt_RelaxedPolyRec] )    -- We want type-sig variables to 
1381                                                         --      be completely rigid for GADTs
1382  , ( Opt_ScopedTypeVariables, [Opt_RelaxedPolyRec] )    -- Ditto for scoped type variables; see
1383                                                         --      Note [Scoped tyvars] in TcBinds
1384   ]
1385
1386 glasgowExtsFlags :: [DynFlag]
1387 glasgowExtsFlags = [
1388              Opt_PrintExplicitForalls
1389            , Opt_ForeignFunctionInterface
1390            , Opt_UnliftedFFITypes
1391            , Opt_GADTs
1392            , Opt_ImplicitParams 
1393            , Opt_ScopedTypeVariables
1394            , Opt_UnboxedTuples
1395            , Opt_TypeSynonymInstances
1396            , Opt_StandaloneDeriving
1397            , Opt_DeriveDataTypeable
1398            , Opt_FlexibleContexts
1399            , Opt_FlexibleInstances
1400            , Opt_ConstrainedClassMethods
1401            , Opt_MultiParamTypeClasses
1402            , Opt_FunctionalDependencies
1403            , Opt_MagicHash
1404            , Opt_PolymorphicComponents
1405            , Opt_ExistentialQuantification
1406            , Opt_UnicodeSyntax
1407            , Opt_PatternGuards
1408            , Opt_LiberalTypeSynonyms
1409            , Opt_RankNTypes
1410            , Opt_ImpredicativeTypes
1411            , Opt_TypeOperators
1412            , Opt_RecursiveDo
1413            , Opt_ParallelListComp
1414            , Opt_EmptyDataDecls
1415            , Opt_KindSignatures
1416            , Opt_PatternSignatures
1417            , Opt_GeneralizedNewtypeDeriving
1418            , Opt_TypeFamilies ]
1419
1420 ------------------
1421 isFlag :: [(String,a)] -> String -> Bool
1422 isFlag flags f = any (\(ff,_) -> ff == f) flags
1423
1424 isPrefFlag :: String -> [(String,a)] -> String -> Bool
1425 isPrefFlag pref flags no_f
1426   | Just f <- maybePrefixMatch pref no_f = isFlag flags f
1427   | otherwise                            = False
1428
1429 ------------------
1430 getFlag :: [(String,a)] -> String -> a
1431 getFlag flags f = case [ opt | (ff, opt) <- flags, ff == f] of
1432                       (o:_)  -> o
1433                       []     -> panic ("get_flag " ++ f)
1434
1435 getPrefFlag :: String -> [(String,a)] -> String -> a
1436 getPrefFlag pref flags f = getFlag flags (fromJust (maybePrefixMatch pref f))
1437 -- We should only be passed flags which match the prefix
1438
1439 -- -----------------------------------------------------------------------------
1440 -- Parsing the dynamic flags.
1441
1442 parseDynamicFlags :: DynFlags -> [String] -> IO (DynFlags,[String])
1443 parseDynamicFlags dflags args = do
1444   let ((leftover,errs),dflags') 
1445           = runCmdLine (processArgs dynamic_flags args) dflags
1446   when (not (null errs)) $ do
1447     throwDyn (UsageError (unlines errs))
1448   return (dflags', leftover)
1449
1450
1451 type DynP = CmdLineP DynFlags
1452
1453 upd :: (DynFlags -> DynFlags) -> DynP ()
1454 upd f = do 
1455    dfs <- getCmdLineState
1456    putCmdLineState $! (f dfs)
1457
1458 --------------------------
1459 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
1460 setDynFlag f = upd (\dfs -> foldl dopt_set (dopt_set dfs f) deps)
1461   where
1462     deps = [ d | (f', ds) <- impliedFlags, f' == f, d <- ds ]
1463         -- When you set f, set the ones it implies
1464         -- When you un-set f, however, we don't un-set the things it implies
1465         --      (except for -fno-glasgow-exts, which is treated specially)
1466
1467 unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
1468
1469 --------------------------
1470 setDumpFlag :: DynFlag -> OptKind DynP
1471 setDumpFlag dump_flag 
1472   = NoArg (setDynFlag Opt_ForceRecomp >> setDynFlag dump_flag)
1473         -- Whenver we -ddump, switch off the recompilation checker,
1474         -- else you don't see the dump!
1475
1476 setVerboseCore2Core :: DynP ()
1477 setVerboseCore2Core = do setDynFlag Opt_ForceRecomp
1478                          setDynFlag Opt_D_verbose_core2core
1479                          upd (\s -> s { shouldDumpSimplPhase = const True })
1480
1481 setDumpSimplPhases :: String -> DynP ()
1482 setDumpSimplPhases s = do setDynFlag Opt_ForceRecomp
1483                           upd (\s -> s { shouldDumpSimplPhase = spec })
1484   where
1485     spec :: SimplifierMode -> Bool
1486     spec = join (||)
1487          . map (join (&&) . map match . split ':')
1488          . split ','
1489          $ case s of
1490              '=' : s' -> s'
1491              _        -> s
1492
1493     join :: (Bool -> Bool -> Bool)
1494          -> [SimplifierMode -> Bool]
1495          -> SimplifierMode -> Bool
1496     join _  [] = const True
1497     join op ss = foldr1 (\f g x -> f x `op` g x) ss
1498
1499     match :: String -> SimplifierMode -> Bool
1500     match "" = const True
1501     match s  = case reads s of
1502                 [(n,"")] -> phase_num  n
1503                 _        -> phase_name s
1504
1505     phase_num :: Int -> SimplifierMode -> Bool
1506     phase_num n (SimplPhase k _) = n == k
1507     phase_num _ _                = False
1508
1509     phase_name :: String -> SimplifierMode -> Bool
1510     phase_name s SimplGently       = s == "gentle"
1511     phase_name s (SimplPhase _ ss) = s `elem` ss
1512
1513 setVerbosity :: Maybe Int -> DynP ()
1514 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
1515
1516 addCmdlineHCInclude :: String -> DynP ()
1517 addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
1518
1519 extraPkgConf_ :: FilePath -> DynP ()
1520 extraPkgConf_  p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s })
1521
1522 exposePackage, hidePackage, ignorePackage :: String -> DynP ()
1523 exposePackage p = 
1524   upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s })
1525 hidePackage p = 
1526   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
1527 ignorePackage p = 
1528   upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s })
1529
1530 setPackageName :: String -> DynFlags -> DynFlags
1531 setPackageName p
1532   | Nothing <- unpackPackageId pid
1533   = throwDyn (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
1534   | otherwise
1535   = \s -> s{ thisPackage = pid }
1536   where
1537         pid = stringToPackageId p
1538
1539 -- If we're linking a binary, then only targets that produce object
1540 -- code are allowed (requests for other target types are ignored).
1541 setTarget :: HscTarget -> DynP ()
1542 setTarget l = upd set
1543   where 
1544    set dfs 
1545      | ghcLink dfs /= LinkBinary || isObjectTarget l  = dfs{ hscTarget = l }
1546      | otherwise = dfs
1547
1548 -- Changes the target only if we're compiling object code.  This is
1549 -- used by -fasm and -fvia-C, which switch from one to the other, but
1550 -- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
1551 -- can be safely used in an OPTIONS_GHC pragma.
1552 setObjTarget :: HscTarget -> DynP ()
1553 setObjTarget l = upd set
1554   where 
1555    set dfs 
1556      | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l }
1557      | otherwise = dfs
1558
1559 setOptLevel :: Int -> DynFlags -> DynFlags
1560 setOptLevel n dflags
1561    | hscTarget dflags == HscInterpreted && n > 0
1562         = dflags
1563             -- not in IO any more, oh well:
1564             -- putStr "warning: -O conflicts with --interactive; -O ignored.\n"
1565    | otherwise
1566         = updOptLevel n dflags
1567
1568
1569 setMainIs :: String -> DynP ()
1570 setMainIs arg
1571   | not (null main_fn) && isLower (head main_fn)
1572      -- The arg looked like "Foo.Bar.baz"
1573   = upd $ \d -> d{ mainFunIs = Just main_fn,
1574                    mainModIs = mkModule mainPackageId (mkModuleName main_mod) }
1575
1576   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
1577   = upd $ \d -> d{ mainModIs = mkModule mainPackageId (mkModuleName arg) }
1578   
1579   | otherwise                   -- The arg looked like "baz"
1580   = upd $ \d -> d{ mainFunIs = Just arg }
1581   where
1582     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
1583
1584 -----------------------------------------------------------------------------
1585 -- Paths & Libraries
1586
1587 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
1588
1589 -- -i on its own deletes the import paths
1590 addImportPath "" = upd (\s -> s{importPaths = []})
1591 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
1592
1593
1594 addLibraryPath p = 
1595   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
1596
1597 addIncludePath p = 
1598   upd (\s -> s{includePaths = includePaths s ++ splitPathList p})
1599
1600 addFrameworkPath p = 
1601   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
1602
1603 #ifndef mingw32_TARGET_OS
1604 split_marker :: Char
1605 split_marker = ':'   -- not configurable (ToDo)
1606 #endif
1607
1608 splitPathList :: String -> [String]
1609 splitPathList s = filter notNull (splitUp s)
1610                 -- empty paths are ignored: there might be a trailing
1611                 -- ':' in the initial list, for example.  Empty paths can
1612                 -- cause confusion when they are translated into -I options
1613                 -- for passing to gcc.
1614   where
1615 #ifndef mingw32_TARGET_OS
1616     splitUp xs = split split_marker xs
1617 #else 
1618      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
1619      -- 
1620      -- That is, if "foo:bar:baz" is used, this interpreted as
1621      -- consisting of three entries, 'foo', 'bar', 'baz'.
1622      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
1623      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
1624      --
1625      -- Notice that no attempt is made to fully replace the 'standard'
1626      -- split marker ':' with the Windows / DOS one, ';'. The reason being
1627      -- that this will cause too much breakage for users & ':' will
1628      -- work fine even with DOS paths, if you're not insisting on being silly.
1629      -- So, use either.
1630     splitUp []             = []
1631     splitUp (x:':':div:xs) | div `elem` dir_markers
1632                            = ((x:':':div:p): splitUp rs)
1633                            where
1634                               (p,rs) = findNextPath xs
1635           -- we used to check for existence of the path here, but that
1636           -- required the IO monad to be threaded through the command-line
1637           -- parser which is quite inconvenient.  The 
1638     splitUp xs = cons p (splitUp rs)
1639                where
1640                  (p,rs) = findNextPath xs
1641     
1642                  cons "" xs = xs
1643                  cons x  xs = x:xs
1644
1645     -- will be called either when we've consumed nought or the
1646     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
1647     -- finding the next split marker.
1648     findNextPath xs = 
1649         case break (`elem` split_markers) xs of
1650            (p, _:ds) -> (p, ds)
1651            (p, xs)   -> (p, xs)
1652
1653     split_markers :: [Char]
1654     split_markers = [':', ';']
1655
1656     dir_markers :: [Char]
1657     dir_markers = ['/', '\\']
1658 #endif
1659
1660 -- -----------------------------------------------------------------------------
1661 -- tmpDir, where we store temporary files.
1662
1663 setTmpDir :: FilePath -> DynFlags -> DynFlags
1664 setTmpDir dir dflags = dflags{ tmpDir = normalise dir }
1665   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
1666   -- seem necessary now --SDM 7/2/2008
1667
1668 -----------------------------------------------------------------------------
1669 -- Hpc stuff
1670
1671 setOptHpcDir :: String -> DynP ()
1672 setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
1673
1674 -----------------------------------------------------------------------------
1675 -- Via-C compilation stuff
1676
1677 -- There are some options that we need to pass to gcc when compiling
1678 -- Haskell code via C, but are only supported by recent versions of
1679 -- gcc.  The configure script decides which of these options we need,
1680 -- and puts them in the file "extra-gcc-opts" in $topdir, which is
1681 -- read before each via-C compilation.  The advantage of having these
1682 -- in a separate file is that the file can be created at install-time
1683 -- depending on the available gcc version, and even re-generated  later
1684 -- if gcc is upgraded.
1685 --
1686 -- The options below are not dependent on the version of gcc, only the
1687 -- platform.
1688
1689 machdepCCOpts :: DynFlags -> ([String], -- flags for all C compilations
1690                               [String]) -- for registerised HC compilations
1691 machdepCCOpts _dflags
1692 #if alpha_TARGET_ARCH
1693         =       ( ["-w", "-mieee"
1694 #ifdef HAVE_THREADED_RTS_SUPPORT
1695                     , "-D_REENTRANT"
1696 #endif
1697                    ], [] )
1698         -- For now, to suppress the gcc warning "call-clobbered
1699         -- register used for global register variable", we simply
1700         -- disable all warnings altogether using the -w flag. Oh well.
1701
1702 #elif hppa_TARGET_ARCH
1703         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
1704         -- (very nice, but too bad the HP /usr/include files don't agree.)
1705         = ( ["-D_HPUX_SOURCE"], [] )
1706
1707 #elif m68k_TARGET_ARCH
1708       -- -fno-defer-pop : for the .hc files, we want all the pushing/
1709       --    popping of args to routines to be explicit; if we let things
1710       --    be deferred 'til after an STGJUMP, imminent death is certain!
1711       --
1712       -- -fomit-frame-pointer : *don't*
1713       --     It's better to have a6 completely tied up being a frame pointer
1714       --     rather than let GCC pick random things to do with it.
1715       --     (If we want to steal a6, then we would try to do things
1716       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
1717         = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
1718
1719 #elif i386_TARGET_ARCH
1720       -- -fno-defer-pop : basically the same game as for m68k
1721       --
1722       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
1723       --   the fp (%ebp) for our register maps.
1724         =  let n_regs = stolen_x86_regs _dflags
1725                sta = opt_Static
1726            in
1727                     ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
1728 --                    , if "mingw32" `isSuffixOf` cTARGETPLATFORM then "-mno-cygwin" else "" 
1729                       ],
1730                       [ "-fno-defer-pop",
1731                         "-fomit-frame-pointer",
1732                         -- we want -fno-builtin, because when gcc inlines
1733                         -- built-in functions like memcpy() it tends to
1734                         -- run out of registers, requiring -monly-n-regs
1735                         "-fno-builtin",
1736                         "-DSTOLEN_X86_REGS="++show n_regs ]
1737                     )
1738
1739 #elif ia64_TARGET_ARCH
1740         = ( [], ["-fomit-frame-pointer", "-G0"] )
1741
1742 #elif x86_64_TARGET_ARCH
1743         = ( [], ["-fomit-frame-pointer",
1744                  "-fno-asynchronous-unwind-tables",
1745                         -- the unwind tables are unnecessary for HC code,
1746                         -- and get in the way of -split-objs.  Another option
1747                         -- would be to throw them away in the mangler, but this
1748                         -- is easier.
1749                  "-fno-builtin"
1750                         -- calling builtins like strlen() using the FFI can
1751                         -- cause gcc to run out of regs, so use the external
1752                         -- version.
1753                 ] )
1754
1755 #elif sparc_TARGET_ARCH
1756         = ( [], ["-w"] )
1757         -- For now, to suppress the gcc warning "call-clobbered
1758         -- register used for global register variable", we simply
1759         -- disable all warnings altogether using the -w flag. Oh well.
1760
1761 #elif powerpc_apple_darwin_TARGET
1762       -- -no-cpp-precomp:
1763       --     Disable Apple's precompiling preprocessor. It's a great thing
1764       --     for "normal" programs, but it doesn't support register variable
1765       --     declarations.
1766         = ( [], ["-no-cpp-precomp"] )
1767 #else
1768         = ( [], [] )
1769 #endif
1770
1771 picCCOpts :: DynFlags -> [String]
1772 picCCOpts _dflags
1773 #if darwin_TARGET_OS
1774       -- Apple prefers to do things the other way round.
1775       -- PIC is on by default.
1776       -- -mdynamic-no-pic:
1777       --     Turn off PIC code generation.
1778       -- -fno-common:
1779       --     Don't generate "common" symbols - these are unwanted
1780       --     in dynamic libraries.
1781
1782     | opt_PIC
1783         = ["-fno-common", "-D__PIC__"]
1784     | otherwise
1785         = ["-mdynamic-no-pic"]
1786 #elif mingw32_TARGET_OS
1787       -- no -fPIC for Windows
1788     | opt_PIC
1789         = ["-D__PIC__"]
1790     | otherwise
1791         = []
1792 #else
1793     | opt_PIC
1794         = ["-fPIC", "-D__PIC__"]
1795     | otherwise
1796         = []
1797 #endif
1798
1799 -- -----------------------------------------------------------------------------
1800 -- Splitting
1801
1802 can_split :: Bool
1803 can_split = cSplitObjs == "YES"
1804
1805 -- -----------------------------------------------------------------------------
1806 -- Compiler Info
1807
1808 compilerInfo :: [(String, String)]
1809 compilerInfo = [("Project name",                cProjectName),
1810                 ("Project version",             cProjectVersion),
1811                 ("Booter version",              cBooterVersion),
1812                 ("Stage",                       cStage),
1813                 ("Interface file version",      cHscIfaceFileVersion),
1814                 ("Have interpreter",            cGhcWithInterpreter),
1815                 ("Object splitting",            cSplitObjs),
1816                 ("Have native code generator",  cGhcWithNativeCodeGen),
1817                 ("Support SMP",                 cGhcWithSMP),
1818                 ("Unregisterised",              cGhcUnregisterised),
1819                 ("Tables next to code",         cGhcEnableTablesNextToCode),
1820                 ("Win32 DLLs",                  cEnableWin32DLLs),
1821                 ("RTS ways",                    cGhcRTSWays),
1822                 ("Leading underscore",          cLeadingUnderscore)]
1823