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