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