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