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