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