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