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