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