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