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