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