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