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