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