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