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