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