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