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