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