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