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