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