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