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