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