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