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