Tidy up the ic_exports field of the InteractiveContext. Previously
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
1 %
2 % (c) The University of Glasgow, 2006
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 -- | Types for the per-module compiler
8 module HscTypes ( 
9         -- * compilation state
10         HscEnv(..), hscEPS,
11         FinderCache, FindResult(..), ModLocationCache,
12         Target(..), TargetId(..), pprTarget, pprTargetId,
13         ModuleGraph, emptyMG,
14
15         -- * Information about modules
16         ModDetails(..), emptyModDetails,
17         ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
18         ImportedMods,
19
20         ModSummary(..), ms_mod_name, showModMsg, isBootSummary,
21         msHsFilePath, msHiFilePath, msObjFilePath,
22
23         -- * Information about the module being compiled
24         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
25         
26         -- * State relating to modules in this package
27         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
28         hptInstances, hptRules, hptVectInfo,
29         hptObjs,
30
31         -- * State relating to known packages
32         ExternalPackageState(..), EpsStats(..), addEpsInStats,
33         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
34         lookupIfaceByModule, emptyModIface,
35         
36         PackageInstEnv, PackageRuleBase,
37
38
39         -- * Annotations
40         prepareAnnotations,
41
42         -- * Interactive context
43         InteractiveContext(..), emptyInteractiveContext, 
44         icPrintUnqual, extendInteractiveContext,
45         substInteractiveContext,
46         mkPrintUnqualified, pprModulePrefix,
47
48         -- * Interfaces
49         ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
50         emptyIfaceWarnCache,
51
52         -- * Fixity
53         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
54
55         -- * TyThings and type environments
56         TyThing(..),
57         tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId, tyThingCoAxiom,
58         implicitTyThings, implicitTyConThings, implicitClassThings, isImplicitTyThing,
59         
60         TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
61         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
62         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
63         typeEnvDataCons, typeEnvCoAxioms,
64
65         -- * MonadThings
66         MonadThings(..),
67
68         -- * Information on imports and exports
69         WhetherHasOrphans, IsBootInterface, Usage(..), 
70         Dependencies(..), noDependencies,
71         NameCache(..), OrigNameCache, OrigIParamCache,
72         Avails, availsToNameSet, availsToNameEnv, availName, availNames,
73         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
74         IfaceExport,
75
76         -- * Warnings
77         Warnings(..), WarningTxt(..), plusWarns,
78
79         -- * Linker stuff
80         Linkable(..), isObjectLinkable, linkableObjs,
81         Unlinked(..), CompiledByteCode,
82         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
83         
84         -- * Program coverage
85         HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
86
87         -- * Breakpoints
88         ModBreaks (..), BreakIndex, emptyModBreaks,
89
90         -- * Vectorisation information
91         VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo, 
92         noIfaceVectInfo,
93
94         -- * Compilation errors and warnings
95         SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
96         throwOneError, handleSourceError,
97         handleFlagWarnings, printOrThrowWarnings,
98     ) where
99
100 #include "HsVersions.h"
101
102 #ifdef GHCI
103 import ByteCodeAsm      ( CompiledByteCode )
104 import {-# SOURCE #-}  InteractiveEval ( Resume )
105 #endif
106
107 import HsSyn
108 import RdrName
109 import Name
110 import NameEnv
111 import NameSet  
112 import Module
113 import InstEnv          ( InstEnv, Instance )
114 import FamInstEnv       ( FamInstEnv, FamInst )
115 import Rules            ( RuleBase )
116 import CoreSyn          ( CoreBind )
117 import VarEnv
118 import Var
119 import Id
120 import Type             
121
122 import Annotations
123 import Class            ( Class, classAllSelIds, classATs, classTyCon )
124 import TyCon
125 import DataCon          ( DataCon, dataConImplicitIds, dataConWrapId )
126 import PrelNames        ( gHC_PRIM )
127 import Packages hiding ( Version(..) )
128 import DynFlags         ( DynFlags(..), isOneShot, HscTarget (..), dopt,
129                           DynFlag(..) )
130 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
131 import BasicTypes       ( IPName, defaultFixity, WarningTxt(..) )
132 import OptimizationFuel ( OptFuelState )
133 import IfaceSyn
134 import CoreSyn          ( CoreRule, CoreVect )
135 import Maybes           ( orElse, expectJust, catMaybes )
136 import Outputable
137 import BreakArray
138 import SrcLoc           ( SrcSpan, Located(..) )
139 import UniqFM           ( lookupUFM, eltsUFM, emptyUFM )
140 import UniqSupply       ( UniqSupply )
141 import FastString
142 import StringBuffer     ( StringBuffer )
143 import Fingerprint
144 import MonadUtils
145 import Data.Dynamic     ( Typeable )
146 import qualified Data.Dynamic as Dyn
147 import Bag
148 import ErrUtils
149
150 import System.FilePath
151 import System.Time      ( ClockTime )
152 import Data.IORef
153 import Data.Array       ( Array, array )
154 import Data.List
155 import Data.Map (Map)
156 import Control.Monad    ( mplus, guard, liftM, when )
157 import Exception
158
159 -- -----------------------------------------------------------------------------
160 -- Source Errors
161
162 -- When the compiler (HscMain) discovers errors, it throws an
163 -- exception in the IO monad.
164
165 mkSrcErr :: ErrorMessages -> SourceError
166 srcErrorMessages :: SourceError -> ErrorMessages
167 mkApiErr :: SDoc -> GhcApiError
168
169 throwOneError :: MonadIO m => ErrMsg -> m ab
170 throwOneError err = liftIO $ throwIO $ mkSrcErr $ unitBag err
171
172 -- | A source error is an error that is caused by one or more errors in the
173 -- source code.  A 'SourceError' is thrown by many functions in the
174 -- compilation pipeline.  Inside GHC these errors are merely printed via
175 -- 'log_action', but API clients may treat them differently, for example,
176 -- insert them into a list box.  If you want the default behaviour, use the
177 -- idiom:
178 --
179 -- > handleSourceError printExceptionAndWarnings $ do
180 -- >   ... api calls that may fail ...
181 --
182 -- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
183 -- This list may be empty if the compiler failed due to @-Werror@
184 -- ('Opt_WarnIsError').
185 --
186 -- See 'printExceptionAndWarnings' for more information on what to take care
187 -- of when writing a custom error handler.
188 data SourceError = SourceError ErrorMessages
189
190 instance Show SourceError where
191   show (SourceError msgs) = unlines . map show . bagToList $ msgs
192     -- ToDo: is there some nicer way to print this?
193
194 sourceErrorTc :: Dyn.TyCon
195 sourceErrorTc = Dyn.mkTyCon "SourceError"
196 {-# NOINLINE sourceErrorTc #-}
197 instance Typeable SourceError where
198   typeOf _ = Dyn.mkTyConApp sourceErrorTc []
199
200 instance Exception SourceError
201
202 mkSrcErr = SourceError
203
204 -- | Perform the given action and call the exception handler if the action
205 -- throws a 'SourceError'.  See 'SourceError' for more information.
206 handleSourceError :: (ExceptionMonad m) =>
207                      (SourceError -> m a) -- ^ exception handler
208                   -> m a -- ^ action to perform
209                   -> m a
210 handleSourceError handler act =
211   gcatch act (\(e :: SourceError) -> handler e)
212
213 srcErrorMessages (SourceError msgs) = msgs
214
215 -- | XXX: what exactly is an API error?
216 data GhcApiError = GhcApiError SDoc
217
218 instance Show GhcApiError where
219   show (GhcApiError msg) = showSDoc msg
220
221 ghcApiErrorTc :: Dyn.TyCon
222 ghcApiErrorTc = Dyn.mkTyCon "GhcApiError"
223 {-# NOINLINE ghcApiErrorTc #-}
224 instance Typeable GhcApiError where
225   typeOf _ = Dyn.mkTyConApp ghcApiErrorTc []
226
227 instance Exception GhcApiError
228
229 mkApiErr = GhcApiError
230
231 -- | Given a bag of warnings, turn them into an exception if
232 -- -Werror is enabled, or print them out otherwise.
233 printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
234 printOrThrowWarnings dflags warns
235   | dopt Opt_WarnIsError dflags
236   = when (not (isEmptyBag warns)) $ do
237       throwIO $ mkSrcErr $ warns `snocBag` warnIsErrorMsg
238   | otherwise
239   = printBagOfWarnings dflags warns
240
241 handleFlagWarnings :: DynFlags -> [Located String] -> IO ()
242 handleFlagWarnings dflags warns
243  = when (dopt Opt_WarnDeprecatedFlags dflags) $ do
244         -- It would be nicer if warns :: [Located Message], but that
245         -- has circular import problems.
246       let bag = listToBag [ mkPlainWarnMsg loc (text warn) 
247                           | L loc warn <- warns ]
248
249       printOrThrowWarnings dflags bag
250 \end{code}
251
252 \begin{code}
253 -- | Hscenv is like 'Session', except that some of the fields are immutable.
254 -- An HscEnv is used to compile a single module from plain Haskell source
255 -- code (after preprocessing) to either C, assembly or C--.  Things like
256 -- the module graph don't change during a single compilation.
257 --
258 -- Historical note: \"hsc\" used to be the name of the compiler binary,
259 -- when there was a separate driver and compiler.  To compile a single
260 -- module, the driver would invoke hsc on the source code... so nowadays
261 -- we think of hsc as the layer of the compiler that deals with compiling
262 -- a single module.
263 data HscEnv 
264   = HscEnv { 
265         hsc_dflags :: DynFlags,
266                 -- ^ The dynamic flag settings
267
268         hsc_targets :: [Target],
269                 -- ^ The targets (or roots) of the current session
270
271         hsc_mod_graph :: ModuleGraph,
272                 -- ^ The module graph of the current session
273
274         hsc_IC :: InteractiveContext,
275                 -- ^ The context for evaluating interactive statements
276
277         hsc_HPT    :: HomePackageTable,
278                 -- ^ The home package table describes already-compiled
279                 -- home-package modules, /excluding/ the module we 
280                 -- are compiling right now.
281                 -- (In one-shot mode the current module is the only
282                 --  home-package module, so hsc_HPT is empty.  All other
283                 --  modules count as \"external-package\" modules.
284                 --  However, even in GHCi mode, hi-boot interfaces are
285                 --  demand-loaded into the external-package table.)
286                 --
287                 -- 'hsc_HPT' is not mutable because we only demand-load 
288                 -- external packages; the home package is eagerly 
289                 -- loaded, module by module, by the compilation manager.
290                 --      
291                 -- The HPT may contain modules compiled earlier by @--make@
292                 -- but not actually below the current module in the dependency
293                 -- graph.
294
295                 -- (This changes a previous invariant: changed Jan 05.)
296         
297         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
298                 -- ^ Information about the currently loaded external packages.
299                 -- This is mutable because packages will be demand-loaded during
300                 -- a compilation run as required.
301         
302         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
303                 -- ^ As with 'hsc_EPS', this is side-effected by compiling to
304                 -- reflect sucking in interface files.  They cache the state of
305                 -- external interface files, in effect.
306
307         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
308                 -- ^ The cached result of performing finding in the file system
309         hsc_MLC  :: {-# UNPACK #-} !(IORef ModLocationCache),
310                 -- ^ This caches the location of modules, so we don't have to 
311                 -- search the filesystem multiple times. See also 'hsc_FC'.
312
313         hsc_OptFuel :: OptFuelState,
314                 -- ^ Settings to control the use of \"optimization fuel\":
315                 -- by limiting the number of transformations,
316                 -- we can use binary search to help find compiler bugs.
317
318         hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
319                 -- ^ Used for one-shot compilation only, to initialise
320                 -- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for 
321                 -- 'TcRunTypes.TcGblEnv'
322  }
323
324 hscEPS :: HscEnv -> IO ExternalPackageState
325 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
326
327 -- | A compilation target.
328 --
329 -- A target may be supplied with the actual text of the
330 -- module.  If so, use this instead of the file contents (this
331 -- is for use in an IDE where the file hasn't been saved by
332 -- the user yet).
333 data Target = Target
334       { targetId           :: TargetId  -- ^ module or filename
335       , targetAllowObjCode :: Bool      -- ^ object code allowed?
336       , targetContents     :: Maybe (StringBuffer,ClockTime)
337                                         -- ^ in-memory text buffer?
338       }
339
340 data TargetId
341   = TargetModule ModuleName
342         -- ^ A module name: search for the file
343   | TargetFile FilePath (Maybe Phase)
344         -- ^ A filename: preprocess & parse it to find the module name.
345         -- If specified, the Phase indicates how to compile this file
346         -- (which phase to start from).  Nothing indicates the starting phase
347         -- should be determined from the suffix of the filename.
348   deriving Eq
349
350 pprTarget :: Target -> SDoc
351 pprTarget (Target id obj _) = 
352    (if obj then char '*' else empty) <> pprTargetId id
353
354 instance Outputable Target where
355     ppr = pprTarget
356
357 pprTargetId :: TargetId -> SDoc
358 pprTargetId (TargetModule m) = ppr m
359 pprTargetId (TargetFile f _) = text f
360
361 instance Outputable TargetId where
362     ppr = pprTargetId
363
364 -- | Helps us find information about modules in the home package
365 type HomePackageTable  = ModuleNameEnv HomeModInfo
366         -- Domain = modules in the home package that have been fully compiled
367         -- "home" package name cached here for convenience
368
369 -- | Helps us find information about modules in the imported packages
370 type PackageIfaceTable = ModuleEnv ModIface
371         -- Domain = modules in the imported packages
372
373 emptyHomePackageTable :: HomePackageTable
374 emptyHomePackageTable  = emptyUFM
375
376 emptyPackageIfaceTable :: PackageIfaceTable
377 emptyPackageIfaceTable = emptyModuleEnv
378
379 -- | Information about modules in the package being compiled
380 data HomeModInfo 
381   = HomeModInfo {
382       hm_iface    :: !ModIface,
383         -- ^ The basic loaded interface file: every loaded module has one of
384         -- these, even if it is imported from another package
385       hm_details  :: !ModDetails,
386         -- ^ Extra information that has been created from the 'ModIface' for
387         -- the module, typically during typechecking
388       hm_linkable :: !(Maybe Linkable)
389         -- ^ The actual artifact we would like to link to access things in
390         -- this module.
391         --
392         -- 'hm_linkable' might be Nothing:
393         --
394         --   1. If this is an .hs-boot module
395         --
396         --   2. Temporarily during compilation if we pruned away
397         --      the old linkable because it was out of date.
398         --
399         -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
400         -- in the 'HomePackageTable' will be @Just@.
401         --
402         -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the
403         -- 'HomeModInfo' by building a new 'ModDetails' from the old
404         -- 'ModIface' (only).
405     }
406
407 -- | Find the 'ModIface' for a 'Module', searching in both the loaded home
408 -- and external package module information
409 lookupIfaceByModule
410         :: DynFlags
411         -> HomePackageTable
412         -> PackageIfaceTable
413         -> Module
414         -> Maybe ModIface
415 lookupIfaceByModule dflags hpt pit mod
416   | modulePackageId mod == thisPackage dflags
417   =     -- The module comes from the home package, so look first
418         -- in the HPT.  If it's not from the home package it's wrong to look
419         -- in the HPT, because the HPT is indexed by *ModuleName* not Module
420     fmap hm_iface (lookupUFM hpt (moduleName mod)) 
421     `mplus` lookupModuleEnv pit mod
422
423   | otherwise = lookupModuleEnv pit mod         -- Look in PIT only 
424
425 -- If the module does come from the home package, why do we look in the PIT as well?
426 -- (a) In OneShot mode, even home-package modules accumulate in the PIT
427 -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
428 --     module is in the PIT, namely GHC.Prim when compiling the base package.
429 -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
430 -- of its own, but it doesn't seem worth the bother.
431 \end{code}
432
433
434 \begin{code}
435 hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
436 -- ^ Find all the instance declarations (of classes and families) that are in
437 -- modules imported by this one, directly or indirectly, and are in the Home
438 -- Package Table.  This ensures that we don't see instances from modules @--make@
439 -- compiled before this one, but which are not below this one.
440 hptInstances hsc_env want_this_module
441   = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
442                 guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
443                 let details = hm_details mod_info
444                 return (md_insts details, md_fam_insts details)
445     in (concat insts, concat famInsts)
446
447 hptVectInfo :: HscEnv -> VectInfo
448 -- ^ Get the combined VectInfo of all modules in the home package table.  In
449 -- contrast to instances and rules, we don't care whether the modules are
450 -- \"below\" us in the dependency sense.  The VectInfo of those modules not \"below\" 
451 -- us does not affect the compilation of the current module.
452 hptVectInfo = concatVectInfo . hptAllThings ((: []) . md_vect_info . hm_details)
453
454 hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
455 -- ^ Get rules from modules \"below\" this one (in the dependency sense)
456 hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
457
458
459 hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
460 -- ^ Get annotations from modules \"below\" this one (in the dependency sense)
461 hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
462 hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
463
464 hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
465 hptAllThings extract hsc_env = concatMap extract (eltsUFM (hsc_HPT hsc_env))
466
467 hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
468 -- Get things from modules \"below\" this one (in the dependency sense)
469 -- C.f Inst.hptInstances
470 hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
471  | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
472   | otherwise
473   = let 
474         hpt = hsc_HPT hsc_env
475     in
476     [ thing
477     |   -- Find each non-hi-boot module below me
478       (mod, is_boot_mod) <- deps
479     , include_hi_boot || not is_boot_mod
480
481         -- unsavoury: when compiling the base package with --make, we
482         -- sometimes try to look up RULES etc for GHC.Prim.  GHC.Prim won't
483         -- be in the HPT, because we never compile it; it's in the EPT
484         -- instead.  ToDo: clean up, and remove this slightly bogus
485         -- filter:
486     , mod /= moduleName gHC_PRIM
487
488         -- Look it up in the HPT
489     , let things = case lookupUFM hpt mod of
490                     Just info -> extract info
491                     Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg [] 
492           msg = vcat [ptext (sLit "missing module") <+> ppr mod,
493                       ptext (sLit "Probable cause: out-of-date interface files")]
494                         -- This really shouldn't happen, but see Trac #962
495
496         -- And get its dfuns
497     , thing <- things ]
498
499 hptObjs :: HomePackageTable -> [FilePath]
500 hptObjs hpt = concat (map (maybe [] linkableObjs . hm_linkable) (eltsUFM hpt))
501 \end{code}
502
503 %************************************************************************
504 %*                                                                      *
505 \subsection{Dealing with Annotations}
506 %*                                                                      *
507 %************************************************************************
508
509 \begin{code}
510 prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
511 -- ^ Deal with gathering annotations in from all possible places 
512 --   and combining them into a single 'AnnEnv'
513 prepareAnnotations hsc_env mb_guts
514   = do { eps <- hscEPS hsc_env
515        ; let -- Extract annotations from the module being compiled if supplied one
516             mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
517         -- Extract dependencies of the module if we are supplied one,
518         -- otherwise load annotations from all home package table
519         -- entries regardless of dependency ordering.
520             home_pkg_anns  = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
521             other_pkg_anns = eps_ann_env eps
522             ann_env        = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns, 
523                                                              Just home_pkg_anns, 
524                                                              Just other_pkg_anns]
525
526        ; return ann_env }
527 \end{code}
528
529 %************************************************************************
530 %*                                                                      *
531 \subsection{The Finder cache}
532 %*                                                                      *
533 %************************************************************************
534
535 \begin{code}
536 -- | The 'FinderCache' maps home module names to the result of
537 -- searching for that module.  It records the results of searching for
538 -- modules along the search path.  On @:load@, we flush the entire
539 -- contents of this cache.
540 --
541 -- Although the @FinderCache@ range is 'FindResult' for convenience ,
542 -- in fact it will only ever contain 'Found' or 'NotFound' entries.
543 --
544 type FinderCache = ModuleNameEnv FindResult
545
546 -- | The result of searching for an imported module.
547 data FindResult
548   = Found ModLocation Module
549         -- ^ The module was found
550   | NoPackage PackageId
551         -- ^ The requested package was not found
552   | FoundMultiple [PackageId]
553         -- ^ _Error_: both in multiple packages
554
555   | NotFound          -- Not found
556       { fr_paths       :: [FilePath]       -- Places where I looked
557
558       , fr_pkg         :: Maybe PackageId  -- Just p => module is in this package's
559                                            --           manifest, but couldn't find
560                                            --           the .hi file
561
562       , fr_mods_hidden :: [PackageId]      -- Module is in these packages,
563                                            --   but the *module* is hidden
564
565       , fr_pkgs_hidden :: [PackageId]      -- Module is in these packages,
566                                            --   but the *package* is hidden
567
568       , fr_suggestions :: [Module]         -- Possible mis-spelled modules
569       }
570
571 -- | Cache that remembers where we found a particular module.  Contains both
572 -- home modules and package modules.  On @:load@, only home modules are
573 -- purged from this cache.
574 type ModLocationCache = ModuleEnv ModLocation
575 \end{code}
576
577 %************************************************************************
578 %*                                                                      *
579 \subsection{Symbol tables and Module details}
580 %*                                                                      *
581 %************************************************************************
582
583 \begin{code}
584 -- | A 'ModIface' plus a 'ModDetails' summarises everything we know 
585 -- about a compiled module.  The 'ModIface' is the stuff *before* linking,
586 -- and can be written out to an interface file. The 'ModDetails is after 
587 -- linking and can be completely recovered from just the 'ModIface'.
588 -- 
589 -- When we read an interface file, we also construct a 'ModIface' from it,
590 -- except that we explicitly make the 'mi_decls' and a few other fields empty;
591 -- as when reading we consolidate the declarations etc. into a number of indexed
592 -- maps and environments in the 'ExternalPackageState'.
593 data ModIface 
594    = ModIface {
595         mi_module   :: !Module,             -- ^ Name of the module we are for
596         mi_iface_hash :: !Fingerprint,      -- ^ Hash of the whole interface
597         mi_mod_hash :: !Fingerprint,        -- ^ Hash of the ABI only
598
599         mi_orphan   :: !WhetherHasOrphans,  -- ^ Whether this module has orphans
600         mi_finsts   :: !WhetherHasFamInst,  -- ^ Whether this module has family instances
601         mi_boot     :: !IsBootInterface,    -- ^ Read from an hi-boot file?
602
603         mi_deps     :: Dependencies,
604                 -- ^ The dependencies of the module.  This is
605                 -- consulted for directly-imported modules, but not
606                 -- for anything else (hence lazy)
607
608         mi_usages   :: [Usage],
609                 -- ^ Usages; kept sorted so that it's easy to decide
610                 -- whether to write a new iface file (changing usages
611                 -- doesn't affect the hash of this module)
612         
613                 -- NOT STRICT!  we read this field lazily from the interface file
614                 -- It is *only* consulted by the recompilation checker
615
616                 -- Exports
617                 -- Kept sorted by (mod,occ), to make version comparisons easier
618         mi_exports  :: ![IfaceExport],
619                 -- ^ Records the modules that are the declaration points for things
620                 -- exported by this module, and the 'OccName's of those things
621         
622         mi_exp_hash :: !Fingerprint,    -- ^ Hash of export list
623
624         mi_fixities :: [(OccName,Fixity)],
625                 -- ^ Fixities
626         
627                 -- NOT STRICT!  we read this field lazily from the interface file
628
629         mi_warns  :: Warnings,
630                 -- ^ Warnings
631                 
632                 -- NOT STRICT!  we read this field lazily from the interface file
633
634         mi_anns  :: [IfaceAnnotation],
635                 -- ^ Annotations
636         
637                 -- NOT STRICT!  we read this field lazily from the interface file
638
639                 -- Type, class and variable declarations
640                 -- The hash of an Id changes if its fixity or deprecations change
641                 --      (as well as its type of course)
642                 -- Ditto data constructors, class operations, except that 
643                 -- the hash of the parent class/tycon changes
644         mi_decls :: [(Fingerprint,IfaceDecl)],  -- ^ Sorted type, variable, class etc. declarations
645
646         mi_globals  :: !(Maybe GlobalRdrEnv),
647                 -- ^ Binds all the things defined at the top level in
648                 -- the /original source/ code for this module. which
649                 -- is NOT the same as mi_exports, nor mi_decls (which
650                 -- may contains declarations for things not actually
651                 -- defined by the user).  Used for GHCi and for inspecting
652                 -- the contents of modules via the GHC API only.
653                 --
654                 -- (We need the source file to figure out the
655                 -- top-level environment, if we didn't compile this module
656                 -- from source then this field contains @Nothing@).
657                 --
658                 -- Strictly speaking this field should live in the
659                 -- 'HomeModInfo', but that leads to more plumbing.
660
661                 -- Instance declarations and rules
662         mi_insts     :: [IfaceInst],                    -- ^ Sorted class instance
663         mi_fam_insts :: [IfaceFamInst],                 -- ^ Sorted family instances
664         mi_rules     :: [IfaceRule],                    -- ^ Sorted rules
665         mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules and 
666                                         -- class and family instances
667                                         -- combined
668
669         mi_vect_info :: !IfaceVectInfo, -- ^ Vectorisation information
670
671                 -- Cached environments for easy lookup
672                 -- These are computed (lazily) from other fields
673                 -- and are not put into the interface file
674         mi_warn_fn  :: Name -> Maybe WarningTxt,        -- ^ Cached lookup for 'mi_warns'
675         mi_fix_fn  :: OccName -> Fixity,                -- ^ Cached lookup for 'mi_fixities'
676         mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint),
677                         -- ^ Cached lookup for 'mi_decls'.
678                         -- The @Nothing@ in 'mi_hash_fn' means that the thing
679                         -- isn't in decls. It's useful to know that when
680                         -- seeing if we are up to date wrt. the old interface.
681                         -- The 'OccName' is the parent of the name, if it has one.
682         mi_hpc    :: !AnyHpcUsage
683                 -- ^ True if this program uses Hpc at any point in the program.
684      }
685
686 -- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
687 -- for home modules only. Information relating to packages will be loaded into
688 -- global environments in 'ExternalPackageState'.
689 data ModDetails
690    = ModDetails {
691         -- The next two fields are created by the typechecker
692         md_exports   :: [AvailInfo],
693         md_types     :: !TypeEnv,       -- ^ Local type environment for this particular module
694         md_insts     :: ![Instance],    -- ^ 'DFunId's for the instances in this module
695         md_fam_insts :: ![FamInst],
696         md_rules     :: ![CoreRule],    -- ^ Domain may include 'Id's from other modules
697         md_anns      :: ![Annotation],  -- ^ Annotations present in this module: currently 
698                                         -- they only annotate things also declared in this module
699         md_vect_info :: !VectInfo       -- ^ Module vectorisation information
700      }
701
702 emptyModDetails :: ModDetails
703 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
704                                md_exports = [],
705                                md_insts     = [],
706                                md_rules     = [],
707                                md_fam_insts = [],
708                                md_anns      = [],
709                                md_vect_info = noVectInfo
710                              } 
711
712 -- | Records the modules directly imported by a module for extracting e.g. usage information
713 type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)]
714 -- TODO: we are not actually using the codomain of this type at all, so it can be
715 -- replaced with ModuleEnv ()
716
717 -- | A ModGuts is carried through the compiler, accumulating stuff as it goes
718 -- There is only one ModGuts at any time, the one for the module
719 -- being compiled right now.  Once it is compiled, a 'ModIface' and 
720 -- 'ModDetails' are extracted and the ModGuts is discarded.
721 data ModGuts
722   = ModGuts {
723         mg_module    :: !Module,         -- ^ Module being compiled
724         mg_boot      :: IsBootInterface, -- ^ Whether it's an hs-boot module
725         mg_exports   :: ![AvailInfo],    -- ^ What it exports
726         mg_deps      :: !Dependencies,   -- ^ What it depends on, directly or
727                                          -- otherwise
728         mg_dir_imps  :: !ImportedMods,   -- ^ Directly-imported modules; used to
729                                          -- generate initialisation code
730         mg_used_names:: !NameSet,        -- ^ What the module needed (used in 'MkIface.mkIface')
731
732         mg_rdr_env   :: !GlobalRdrEnv,   -- ^ Top-level lexical environment
733
734         -- These fields all describe the things **declared in this module**
735         mg_fix_env   :: !FixityEnv,      -- ^ Fixities declared in this module
736                                          -- TODO: I'm unconvinced this is actually used anywhere
737         mg_types     :: !TypeEnv,        -- ^ Types declared in this module
738         mg_insts     :: ![Instance],     -- ^ Class instances declared in this module
739         mg_fam_insts :: ![FamInst],      -- ^ Family instances declared in this module
740         mg_rules     :: ![CoreRule],     -- ^ Before the core pipeline starts, contains 
741                                          -- See Note [Overall plumbing for rules] in Rules.lhs
742         mg_binds     :: ![CoreBind],     -- ^ Bindings for this module
743         mg_foreign   :: !ForeignStubs,   -- ^ Foreign exports declared in this module
744         mg_warns     :: !Warnings,       -- ^ Warnings declared in the module
745         mg_anns      :: [Annotation],    -- ^ Annotations declared in this module
746         mg_hpc_info  :: !HpcInfo,        -- ^ Coverage tick boxes in the module
747         mg_modBreaks :: !ModBreaks,      -- ^ Breakpoints for the module
748         mg_vect_decls:: ![CoreVect],     -- ^ Vectorisation declarations in this module
749                                          --   (produced by desugarer & consumed by vectoriser)
750         mg_vect_info :: !VectInfo,       -- ^ Pool of vectorised declarations in the module
751
752         -- The next two fields are unusual, because they give instance
753         -- environments for *all* modules in the home package, including
754         -- this module, rather than for *just* this module.  
755         -- Reason: when looking up an instance we don't want to have to
756         --        look at each module in the home package in turn
757         mg_inst_env     :: InstEnv,
758         -- ^ Class instance environment from /home-package/ modules (including
759         -- this one); c.f. 'tcg_inst_env'
760         mg_fam_inst_env :: FamInstEnv
761         -- ^ Type-family instance enviroment for /home-package/ modules
762         -- (including this one); c.f. 'tcg_fam_inst_env'
763     }
764
765 -- The ModGuts takes on several slightly different forms:
766 --
767 -- After simplification, the following fields change slightly:
768 --      mg_rules        Orphan rules only (local ones now attached to binds)
769 --      mg_binds        With rules attached
770
771 -- The ModGuts takes on several slightly different forms:
772 --
773 -- After simplification, the following fields change slightly:
774 --      mg_rules        Orphan rules only (local ones now attached to binds)
775 --      mg_binds        With rules attached
776
777
778 ---------------------------------------------------------
779 -- The Tidy pass forks the information about this module: 
780 --      * one lot goes to interface file generation (ModIface)
781 --        and later compilations (ModDetails)
782 --      * the other lot goes to code generation (CgGuts)
783
784 -- | A restricted form of 'ModGuts' for code generation purposes
785 data CgGuts 
786   = CgGuts {
787         cg_module   :: !Module, -- ^ Module being compiled
788
789         cg_tycons   :: [TyCon],
790                 -- ^ Algebraic data types (including ones that started
791                 -- life as classes); generate constructors and info
792                 -- tables. Includes newtypes, just for the benefit of
793                 -- External Core
794
795         cg_binds    :: [CoreBind],
796                 -- ^ The tidied main bindings, including
797                 -- previously-implicit bindings for record and class
798                 -- selectors, and data construtor wrappers.  But *not*
799                 -- data constructor workers; reason: we we regard them
800                 -- as part of the code-gen of tycons
801
802         cg_foreign  :: !ForeignStubs,   -- ^ Foreign export stubs
803         cg_dep_pkgs :: ![PackageId],    -- ^ Dependent packages, used to 
804                                         -- generate #includes for C code gen
805         cg_hpc_info :: !HpcInfo,        -- ^ Program coverage tick box information
806         cg_modBreaks :: !ModBreaks      -- ^ Module breakpoints
807     }
808
809 -----------------------------------
810 -- | Foreign export stubs
811 data ForeignStubs = NoStubs             -- ^ We don't have any stubs
812                   | ForeignStubs
813                         SDoc            
814                         SDoc            
815                    -- ^ There are some stubs. Parameters:
816                    --
817                    --  1) Header file prototypes for
818                    --     "foreign exported" functions
819                    --
820                    --  2) C stubs to use when calling
821                    --     "foreign exported" functions
822
823 appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
824 appendStubC NoStubs            c_code = ForeignStubs empty c_code
825 appendStubC (ForeignStubs h c) c_code = ForeignStubs h (c $$ c_code)
826 \end{code}
827
828 \begin{code}
829 emptyModIface :: Module -> ModIface
830 emptyModIface mod
831   = ModIface { mi_module   = mod,
832                mi_iface_hash = fingerprint0,
833                mi_mod_hash = fingerprint0,
834                mi_orphan   = False,
835                mi_finsts   = False,
836                mi_boot     = False,
837                mi_deps     = noDependencies,
838                mi_usages   = [],
839                mi_exports  = [],
840                mi_exp_hash = fingerprint0,
841                mi_fixities = [],
842                mi_warns    = NoWarnings,
843                mi_anns     = [],
844                mi_insts     = [],
845                mi_fam_insts = [],
846                mi_rules     = [],
847                mi_decls     = [],
848                mi_globals   = Nothing,
849                mi_orphan_hash = fingerprint0,
850                mi_vect_info = noIfaceVectInfo,
851                mi_warn_fn    = emptyIfaceWarnCache,
852                mi_fix_fn    = emptyIfaceFixCache,
853                mi_hash_fn   = emptyIfaceHashCache,
854                mi_hpc       = False
855     }           
856 \end{code}
857
858
859 %************************************************************************
860 %*                                                                      *
861 \subsection{The interactive context}
862 %*                                                                      *
863 %************************************************************************
864
865 \begin{code}
866 -- | Interactive context, recording information about the state of the
867 -- context in which statements are executed in a GHC session.
868 --
869 data InteractiveContext 
870   = InteractiveContext { 
871          -- These two fields are only stored here so that the client
872          -- can retrieve them with GHC.getContext.  GHC itself doesn't
873          -- use them, but it does reset them to empty sometimes (such
874          -- as before a GHC.load).  The context is set with GHC.setContext.
875          ic_toplev_scope :: [Module],
876              -- ^ The context includes the "top-level" scope of
877              -- these modules
878          ic_imports :: [ImportDecl RdrName],
879              -- ^ The context is extended with these import declarations
880
881          ic_rn_gbl_env :: GlobalRdrEnv,
882              -- ^ The contexts' cached 'GlobalRdrEnv', built by
883              -- 'InteractiveEval.setContext'
884
885          ic_tmp_ids :: [Id],
886              -- ^ Names bound during interaction with the user.  Later
887              -- Ids shadow earlier ones with the same OccName
888              -- Expressions are typed with these Ids in the envt For
889              -- runtime-debugging, these Ids may have free TcTyVars of
890              -- RuntimUnkSkol flavour, but no free TyVars (because the
891              -- typechecker doesn't expect that)
892
893 #ifdef GHCI
894          ic_resume :: [Resume],
895              -- ^ The stack of breakpoint contexts
896 #endif
897
898          ic_cwd :: Maybe FilePath
899              -- virtual CWD of the program
900     }
901
902
903 emptyInteractiveContext :: InteractiveContext
904 emptyInteractiveContext
905   = InteractiveContext { ic_toplev_scope = [],
906                          ic_imports = [],
907                          ic_rn_gbl_env = emptyGlobalRdrEnv,
908                          ic_tmp_ids = []
909 #ifdef GHCI
910                          , ic_resume = []
911 #endif
912                          , ic_cwd = Nothing
913                        }
914
915 icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
916 icPrintUnqual dflags ictxt = mkPrintUnqualified dflags (ic_rn_gbl_env ictxt)
917
918
919 extendInteractiveContext
920         :: InteractiveContext
921         -> [Id]
922         -> InteractiveContext
923 extendInteractiveContext ictxt ids
924   = ictxt { ic_tmp_ids =  snub ((ic_tmp_ids ictxt \\ ids) ++ ids)
925                           -- NB. must be this way around, because we want
926                           -- new ids to shadow existing bindings.
927           }
928     where snub = map head . group . sort
929
930 substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
931 substInteractiveContext ictxt subst | isEmptyTvSubst subst = ictxt
932 substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst 
933   = ictxt { ic_tmp_ids = map subst_ty ids }
934   where
935    subst_ty id = id `setIdType` substTy subst (idType id)
936 \end{code}
937
938 %************************************************************************
939 %*                                                                      *
940         Building a PrintUnqualified             
941 %*                                                                      *
942 %************************************************************************
943
944 Note [Printing original names]
945 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
946 Deciding how to print names is pretty tricky.  We are given a name
947 P:M.T, where P is the package name, M is the defining module, and T is
948 the occurrence name, and we have to decide in which form to display
949 the name given a GlobalRdrEnv describing the current scope.
950
951 Ideally we want to display the name in the form in which it is in
952 scope.  However, the name might not be in scope at all, and that's
953 where it gets tricky.  Here are the cases:
954
955  1. T uniquely maps to  P:M.T      --->  "T"      NameUnqual
956  2. There is an X for which X.T 
957        uniquely maps to  P:M.T     --->  "X.T"    NameQual X
958  3. There is no binding for "M.T"  --->  "M.T"    NameNotInScope1
959  4. Otherwise                      --->  "P:M.T"  NameNotInScope2
960
961 (3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at
962 all. In these cases we still want to refer to the name as "M.T", *but*
963 "M.T" might mean something else in the current scope (e.g. if there's
964 an "import X as M"), so to avoid confusion we avoid using "M.T" if
965 there's already a binding for it.  Instead we write P:M.T.
966
967 There's one further subtlety: in case (3), what if there are two
968 things around, P1:M.T and P2:M.T?  Then we don't want to print both of
969 them as M.T!  However only one of the modules P1:M and P2:M can be
970 exposed (say P2), so we use M.T for that, and P1:M.T for the other one.
971 This is handled by the qual_mod component of PrintUnqualified, inside
972 the (ppr mod) of case (3), in Name.pprModulePrefix
973
974 \begin{code}
975 -- | Creates some functions that work out the best ways to format
976 -- names for the user according to a set of heuristics
977 mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
978 mkPrintUnqualified dflags env = (qual_name, qual_mod)
979   where
980   qual_name mod occ     -- The (mod,occ) pair is the original name of the thing
981         | [gre] <- unqual_gres, right_name gre = NameUnqual
982                 -- If there's a unique entity that's in scope unqualified with 'occ'
983                 -- AND that entity is the right one, then we can use the unqualified name
984
985         | [gre] <- qual_gres = NameQual (get_qual_mod (gre_prov gre))
986
987         | null qual_gres = 
988               if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
989                    then NameNotInScope1
990                    else NameNotInScope2
991
992         | otherwise = panic "mkPrintUnqualified"
993       where
994         right_name gre = nameModule_maybe (gre_name gre) == Just mod
995
996         unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
997         qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
998
999         get_qual_mod LocalDef      = moduleName mod
1000         get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
1001
1002     -- we can mention a module P:M without the P: qualifier iff
1003     -- "import M" would resolve unambiguously to P:M.  (if P is the
1004     -- current package we can just assume it is unqualified).
1005
1006   qual_mod mod
1007      | modulePackageId mod == thisPackage dflags = False
1008
1009      | [pkgconfig] <- [pkg | (pkg,exposed_module) <- lookup, 
1010                              exposed pkg && exposed_module],
1011        packageConfigId pkgconfig == modulePackageId mod
1012         -- this says: we are given a module P:M, is there just one exposed package
1013         -- that exposes a module M, and is it package P?
1014      = False
1015
1016      | otherwise = True
1017      where lookup = lookupModuleInAllPackages dflags (moduleName mod)
1018 \end{code}
1019
1020
1021 %************************************************************************
1022 %*                                                                      *
1023                 TyThing
1024 %*                                                                      *
1025 %************************************************************************
1026
1027 \begin{code}
1028 -- | Determine the 'TyThing's brought into scope by another 'TyThing'
1029 -- /other/ than itself. For example, Id's don't have any implicit TyThings
1030 -- as they just bring themselves into scope, but classes bring their
1031 -- dictionary datatype, type constructor and some selector functions into
1032 -- scope, just for a start!
1033
1034 -- N.B. the set of TyThings returned here *must* match the set of
1035 -- names returned by LoadIface.ifaceDeclSubBndrs, in the sense that
1036 -- TyThing.getOccName should define a bijection between the two lists.
1037 -- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop])
1038 -- The order of the list does not matter.
1039 implicitTyThings :: TyThing -> [TyThing]
1040 implicitTyThings (AnId _)       = []
1041 implicitTyThings (ACoAxiom _cc) = []
1042 implicitTyThings (ATyCon tc)    = implicitTyConThings tc
1043 implicitTyThings (AClass cl)    = implicitClassThings cl
1044 implicitTyThings (ADataCon dc)  = map AnId (dataConImplicitIds dc)
1045     -- For data cons add the worker and (possibly) wrapper
1046     
1047 implicitClassThings :: Class -> [TyThing]
1048 implicitClassThings cl 
1049   = -- Does not include default methods, because those Ids may have
1050     --    their own pragmas, unfoldings etc, not derived from the Class object
1051     -- Dictionary datatype:
1052     --    [extras_plus:]
1053     --      type constructor 
1054     --    [recursive call:]
1055     --      (possibly) newtype coercion; definitely no family coercion here
1056     --      data constructor
1057     --      worker
1058     --      (no wrapper by invariant)
1059     extras_plus (ATyCon (classTyCon cl)) ++
1060     -- associated types 
1061     --    No extras_plus (recursive call) for the classATs, because they
1062     --    are only the family decls; they have no implicit things
1063     map ATyCon (classATs cl) ++
1064     -- superclass and operation selectors
1065     map AnId (classAllSelIds cl)
1066
1067 implicitTyConThings :: TyCon -> [TyThing]
1068 implicitTyConThings tc 
1069   =   -- fields (names of selectors)
1070       -- (possibly) implicit coercion and family coercion
1071       --   depending on whether it's a newtype or a family instance or both
1072     implicitCoTyCon tc ++
1073       -- for each data constructor in order,
1074       --   the contructor, worker, and (possibly) wrapper
1075     concatMap (extras_plus . ADataCon) (tyConDataCons tc)
1076
1077
1078 -- add a thing and recursive call
1079 extras_plus :: TyThing -> [TyThing]
1080 extras_plus thing = thing : implicitTyThings thing
1081
1082 -- For newtypes and indexed data types (and both),
1083 -- add the implicit coercion tycon
1084 implicitCoTyCon :: TyCon -> [TyThing]
1085 implicitCoTyCon tc 
1086   = map ACoAxiom . catMaybes $ [-- Just if newtype, Nothing if not
1087                               newTyConCo_maybe tc,
1088                               -- Just if family instance, Nothing if not
1089                               tyConFamilyCoercion_maybe tc] 
1090
1091 -- sortByOcc = sortBy (\ x -> \ y -> getOccName x < getOccName y)
1092
1093
1094 -- | Returns @True@ if there should be no interface-file declaration
1095 -- for this thing on its own: either it is built-in, or it is part
1096 -- of some other declaration, or it is generated implicitly by some
1097 -- other declaration.
1098 isImplicitTyThing :: TyThing -> Bool
1099 isImplicitTyThing (ADataCon {}) = True
1100 isImplicitTyThing (AnId id)     = isImplicitId id
1101 isImplicitTyThing (AClass {})   = False
1102 isImplicitTyThing (ATyCon tc)   = isImplicitTyCon tc
1103 isImplicitTyThing (ACoAxiom {}) = True
1104
1105 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
1106 extendTypeEnvWithIds env ids
1107   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
1108 \end{code}
1109
1110 %************************************************************************
1111 %*                                                                      *
1112                 TypeEnv
1113 %*                                                                      *
1114 %************************************************************************
1115
1116 \begin{code}
1117 -- | A map from 'Name's to 'TyThing's, constructed by typechecking
1118 -- local declarations or interface files
1119 type TypeEnv = NameEnv TyThing
1120
1121 emptyTypeEnv    :: TypeEnv
1122 typeEnvElts     :: TypeEnv -> [TyThing]
1123 typeEnvClasses  :: TypeEnv -> [Class]
1124 typeEnvTyCons   :: TypeEnv -> [TyCon]
1125 typeEnvCoAxioms :: TypeEnv -> [CoAxiom]
1126 typeEnvIds      :: TypeEnv -> [Id]
1127 typeEnvDataCons :: TypeEnv -> [DataCon]
1128 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
1129
1130 emptyTypeEnv        = emptyNameEnv
1131 typeEnvElts     env = nameEnvElts env
1132 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
1133 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
1134 typeEnvCoAxioms env = [ax | ACoAxiom ax <- typeEnvElts env] 
1135 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
1136 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
1137
1138 mkTypeEnv :: [TyThing] -> TypeEnv
1139 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
1140                 
1141 lookupTypeEnv = lookupNameEnv
1142
1143 -- Extend the type environment
1144 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
1145 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
1146
1147 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
1148 extendTypeEnvList env things = foldl extendTypeEnv env things
1149 \end{code}
1150
1151 \begin{code}
1152 -- | Find the 'TyThing' for the given 'Name' by using all the resources
1153 -- at our disposal: the compiled modules in the 'HomePackageTable' and the
1154 -- compiled modules in other packages that live in 'PackageTypeEnv'. Note
1155 -- that this does NOT look up the 'TyThing' in the module being compiled: you
1156 -- have to do that yourself, if desired
1157 lookupType :: DynFlags
1158            -> HomePackageTable
1159            -> PackageTypeEnv
1160            -> Name
1161            -> Maybe TyThing
1162
1163 lookupType dflags hpt pte name
1164   -- in one-shot, we don't use the HPT
1165   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
1166   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
1167        lookupNameEnv (md_types (hm_details hm)) name
1168   | otherwise
1169   = lookupNameEnv pte name
1170   where mod = ASSERT( isExternalName name ) nameModule name
1171         this_pkg = thisPackage dflags
1172
1173 -- | As 'lookupType', but with a marginally easier-to-use interface
1174 -- if you have a 'HscEnv'
1175 lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
1176 lookupTypeHscEnv hsc_env name = do
1177     eps <- readIORef (hsc_EPS hsc_env)
1178     return $! lookupType dflags hpt (eps_PTE eps) name
1179   where 
1180     dflags = hsc_dflags hsc_env
1181     hpt = hsc_HPT hsc_env
1182 \end{code}
1183
1184 \begin{code}
1185 -- | Get the 'TyCon' from a 'TyThing' if it is a type constructor thing. Panics otherwise
1186 tyThingTyCon :: TyThing -> TyCon
1187 tyThingTyCon (ATyCon tc) = tc
1188 tyThingTyCon other       = pprPanic "tyThingTyCon" (pprTyThing other)
1189
1190 -- | Get the 'CoAxiom' from a 'TyThing' if it is a coercion axiom thing. Panics otherwise
1191 tyThingCoAxiom :: TyThing -> CoAxiom
1192 tyThingCoAxiom (ACoAxiom ax) = ax
1193 tyThingCoAxiom other         = pprPanic "tyThingCoAxiom" (pprTyThing other)
1194
1195 -- | Get the 'Class' from a 'TyThing' if it is a class thing. Panics otherwise
1196 tyThingClass :: TyThing -> Class
1197 tyThingClass (AClass cls) = cls
1198 tyThingClass other        = pprPanic "tyThingClass" (pprTyThing other)
1199
1200 -- | Get the 'DataCon' from a 'TyThing' if it is a data constructor thing. Panics otherwise
1201 tyThingDataCon :: TyThing -> DataCon
1202 tyThingDataCon (ADataCon dc) = dc
1203 tyThingDataCon other         = pprPanic "tyThingDataCon" (pprTyThing other)
1204
1205 -- | Get the 'Id' from a 'TyThing' if it is a id *or* data constructor thing. Panics otherwise
1206 tyThingId :: TyThing -> Id
1207 tyThingId (AnId id)     = id
1208 tyThingId (ADataCon dc) = dataConWrapId dc
1209 tyThingId other         = pprPanic "tyThingId" (pprTyThing other)
1210 \end{code}
1211
1212 %************************************************************************
1213 %*                                                                      *
1214 \subsection{MonadThings and friends}
1215 %*                                                                      *
1216 %************************************************************************
1217
1218 \begin{code}
1219 -- | Class that abstracts out the common ability of the monads in GHC
1220 -- to lookup a 'TyThing' in the monadic environment by 'Name'. Provides
1221 -- a number of related convenience functions for accessing particular
1222 -- kinds of 'TyThing'
1223 class Monad m => MonadThings m where
1224         lookupThing :: Name -> m TyThing
1225
1226         lookupId :: Name -> m Id
1227         lookupId = liftM tyThingId . lookupThing
1228
1229         lookupDataCon :: Name -> m DataCon
1230         lookupDataCon = liftM tyThingDataCon . lookupThing
1231
1232         lookupTyCon :: Name -> m TyCon
1233         lookupTyCon = liftM tyThingTyCon . lookupThing
1234
1235         lookupClass :: Name -> m Class
1236         lookupClass = liftM tyThingClass . lookupThing
1237 \end{code}
1238
1239 \begin{code}
1240 -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
1241 mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
1242                  -> (OccName -> Maybe (OccName, Fingerprint))
1243 mkIfaceHashCache pairs 
1244   = \occ -> lookupOccEnv env occ
1245   where
1246     env = foldr add_decl emptyOccEnv pairs
1247     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
1248       where
1249           decl_name = ifName d
1250           env1 = extendOccEnv env0 decl_name (decl_name, v)
1251           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
1252
1253 emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
1254 emptyIfaceHashCache _occ = Nothing
1255 \end{code}
1256
1257 %************************************************************************
1258 %*                                                                      *
1259 \subsection{Auxiliary types}
1260 %*                                                                      *
1261 %************************************************************************
1262
1263 These types are defined here because they are mentioned in ModDetails,
1264 but they are mostly elaborated elsewhere
1265
1266 \begin{code}
1267 ------------------ Warnings -------------------------
1268 -- | Warning information for a module
1269 data Warnings
1270   = NoWarnings                          -- ^ Nothing deprecated
1271   | WarnAll WarningTxt                  -- ^ Whole module deprecated
1272   | WarnSome [(OccName,WarningTxt)]     -- ^ Some specific things deprecated
1273
1274      -- Only an OccName is needed because
1275      --    (1) a deprecation always applies to a binding
1276      --        defined in the module in which the deprecation appears.
1277      --    (2) deprecations are only reported outside the defining module.
1278      --        this is important because, otherwise, if we saw something like
1279      --
1280      --        {-# DEPRECATED f "" #-}
1281      --        f = ...
1282      --        h = f
1283      --        g = let f = undefined in f
1284      --
1285      --        we'd need more information than an OccName to know to say something
1286      --        about the use of f in h but not the use of the locally bound f in g
1287      --
1288      --        however, because we only report about deprecations from the outside,
1289      --        and a module can only export one value called f,
1290      --        an OccName suffices.
1291      --
1292      --        this is in contrast with fixity declarations, where we need to map
1293      --        a Name to its fixity declaration.
1294   deriving( Eq )
1295
1296 -- | Constructs the cache for the 'mi_warn_fn' field of a 'ModIface'
1297 mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt
1298 mkIfaceWarnCache NoWarnings  = \_ -> Nothing
1299 mkIfaceWarnCache (WarnAll t) = \_ -> Just t
1300 mkIfaceWarnCache (WarnSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
1301
1302 emptyIfaceWarnCache :: Name -> Maybe WarningTxt
1303 emptyIfaceWarnCache _ = Nothing
1304
1305 plusWarns :: Warnings -> Warnings -> Warnings
1306 plusWarns d NoWarnings = d
1307 plusWarns NoWarnings d = d
1308 plusWarns _ (WarnAll t) = WarnAll t
1309 plusWarns (WarnAll t) _ = WarnAll t
1310 plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
1311 \end{code}
1312 \begin{code}
1313 -- | A collection of 'AvailInfo' - several things that are \"available\"
1314 type Avails       = [AvailInfo]
1315 -- | 'Name'd things that are available
1316 type AvailInfo    = GenAvailInfo Name
1317 -- | 'RdrName'd things that are available
1318 type RdrAvailInfo = GenAvailInfo OccName
1319
1320 -- | Records what things are "available", i.e. in scope
1321 data GenAvailInfo name  = Avail name     -- ^ An ordinary identifier in scope
1322                         | AvailTC name
1323                                   [name] -- ^ A type or class in scope. Parameters:
1324                                          --
1325                                          --  1) The name of the type or class
1326                                          --
1327                                          --  2) The available pieces of type or class.
1328                                          --     NB: If the type or class is itself
1329                                          --     to be in scope, it must be in this list.
1330                                          --     Thus, typically: @AvailTC Eq [Eq, ==, \/=]@
1331                         deriving( Eq )
1332                         -- Equality used when deciding if the interface has changed
1333
1334 -- | The original names declared of a certain module that are exported
1335 type IfaceExport = (Module, [GenAvailInfo OccName])
1336
1337 availsToNameSet :: [AvailInfo] -> NameSet
1338 availsToNameSet avails = foldr add emptyNameSet avails
1339       where add avail set = addListToNameSet set (availNames avail)
1340
1341 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
1342 availsToNameEnv avails = foldr add emptyNameEnv avails
1343      where add avail env = extendNameEnvList env
1344                                 (zip (availNames avail) (repeat avail))
1345
1346 -- | Just the main name made available, i.e. not the available pieces
1347 -- of type or class brought into scope by the 'GenAvailInfo'
1348 availName :: GenAvailInfo name -> name
1349 availName (Avail n)     = n
1350 availName (AvailTC n _) = n
1351
1352 -- | All names made available by the availability information
1353 availNames :: GenAvailInfo name -> [name]
1354 availNames (Avail n)      = [n]
1355 availNames (AvailTC _ ns) = ns
1356
1357 instance Outputable n => Outputable (GenAvailInfo n) where
1358    ppr = pprAvail
1359
1360 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
1361 pprAvail (Avail n)      = ppr n
1362 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
1363 \end{code}
1364
1365 \begin{code}
1366 -- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface'
1367 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
1368 mkIfaceFixCache pairs 
1369   = \n -> lookupOccEnv env n `orElse` defaultFixity
1370   where
1371    env = mkOccEnv pairs
1372
1373 emptyIfaceFixCache :: OccName -> Fixity
1374 emptyIfaceFixCache _ = defaultFixity
1375
1376 -- | Fixity environment mapping names to their fixities
1377 type FixityEnv = NameEnv FixItem
1378
1379 -- | Fixity information for an 'Name'. We keep the OccName in the range 
1380 -- so that we can generate an interface from it
1381 data FixItem = FixItem OccName Fixity
1382
1383 instance Outputable FixItem where
1384   ppr (FixItem occ fix) = ppr fix <+> ppr occ
1385
1386 emptyFixityEnv :: FixityEnv
1387 emptyFixityEnv = emptyNameEnv
1388
1389 lookupFixity :: FixityEnv -> Name -> Fixity
1390 lookupFixity env n = case lookupNameEnv env n of
1391                         Just (FixItem _ fix) -> fix
1392                         Nothing         -> defaultFixity
1393 \end{code}
1394
1395
1396 %************************************************************************
1397 %*                                                                      *
1398 \subsection{WhatsImported}
1399 %*                                                                      *
1400 %************************************************************************
1401
1402 \begin{code}
1403 -- | Records whether a module has orphans. An \"orphan\" is one of:
1404 --
1405 -- * An instance declaration in a module other than the definition
1406 --   module for one of the type constructors or classes in the instance head
1407 --
1408 -- * A transformation rule in a module other than the one defining
1409 --   the function in the head of the rule
1410 type WhetherHasOrphans   = Bool
1411
1412 -- | Does this module define family instances?
1413 type WhetherHasFamInst = Bool
1414
1415 -- | Did this module originate from a *-boot file?
1416 type IsBootInterface = Bool
1417
1418 -- | Dependency information about modules and packages below this one
1419 -- in the import hierarchy.
1420 --
1421 -- Invariant: the dependencies of a module @M@ never includes @M@.
1422 --
1423 -- Invariant: none of the lists contain duplicates.
1424 data Dependencies
1425   = Deps { dep_mods   :: [(ModuleName, IsBootInterface)]
1426                         -- ^ Home-package module dependencies
1427          , dep_pkgs   :: [PackageId]
1428                         -- ^ External package dependencies
1429          , dep_orphs  :: [Module]           
1430                         -- ^ Orphan modules (whether home or external pkg),
1431                         -- *not* including family instance orphans as they
1432                         -- are anyway included in 'dep_finsts'
1433          , dep_finsts :: [Module]           
1434                         -- ^ Modules that contain family instances (whether the
1435                         -- instances are from the home or an external package)
1436          }
1437   deriving( Eq )
1438         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1439
1440         -- See 'TcRnTypes.ImportAvails' for details on dependencies.
1441
1442 noDependencies :: Dependencies
1443 noDependencies = Deps [] [] [] []
1444
1445 -- | Records modules that we depend on by making a direct import from
1446 data Usage
1447   = UsagePackageModule {
1448         usg_mod      :: Module,
1449            -- ^ External package module depended on
1450         usg_mod_hash :: Fingerprint
1451     }                                           -- ^ Module from another package
1452   | UsageHomeModule {
1453         usg_mod_name :: ModuleName,
1454             -- ^ Name of the module
1455         usg_mod_hash :: Fingerprint,
1456             -- ^ Cached module fingerprint
1457         usg_entities :: [(OccName,Fingerprint)],
1458             -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
1459             -- NB: usages are for parent names only, e.g. type constructors 
1460             -- but not the associated data constructors.
1461         usg_exports  :: Maybe Fingerprint
1462             -- ^ Fingerprint for the export list we used to depend on this module,
1463             -- if we depend on the export list
1464     }                                           -- ^ Module from the current package
1465     deriving( Eq )
1466         -- The export list field is (Just v) if we depend on the export list:
1467         --      i.e. we imported the module directly, whether or not we
1468         --           enumerated the things we imported, or just imported 
1469         --           everything
1470         -- We need to recompile if M's exports change, because 
1471         -- if the import was    import M,       we might now have a name clash
1472         --                                      in the importing module.
1473         -- if the import was    import M(x)     M might no longer export x
1474         -- The only way we don't depend on the export list is if we have
1475         --                      import M()
1476         -- And of course, for modules that aren't imported directly we don't
1477         -- depend on their export lists
1478 \end{code}
1479
1480
1481 %************************************************************************
1482 %*                                                                      *
1483                 The External Package State
1484 %*                                                                      *
1485 %************************************************************************
1486
1487 \begin{code}
1488 type PackageTypeEnv    = TypeEnv
1489 type PackageRuleBase   = RuleBase
1490 type PackageInstEnv    = InstEnv
1491 type PackageFamInstEnv = FamInstEnv
1492 type PackageVectInfo   = VectInfo
1493 type PackageAnnEnv     = AnnEnv
1494
1495 -- | Information about other packages that we have slurped in by reading
1496 -- their interface files
1497 data ExternalPackageState
1498   = EPS {
1499         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1500                 -- ^ In OneShot mode (only), home-package modules
1501                 -- accumulate in the external package state, and are
1502                 -- sucked in lazily.  For these home-pkg modules
1503                 -- (only) we need to record which are boot modules.
1504                 -- We set this field after loading all the
1505                 -- explicitly-imported interfaces, but before doing
1506                 -- anything else
1507                 --
1508                 -- The 'ModuleName' part is not necessary, but it's useful for
1509                 -- debug prints, and it's convenient because this field comes
1510                 -- direct from 'TcRnTypes.imp_dep_mods'
1511
1512         eps_PIT :: !PackageIfaceTable,
1513                 -- ^ The 'ModIface's for modules in external packages
1514                 -- whose interfaces we have opened.
1515                 -- The declarations in these interface files are held in the
1516                 -- 'eps_decls', 'eps_inst_env', 'eps_fam_inst_env' and 'eps_rules'
1517                 -- fields of this record, not in the 'mi_decls' fields of the 
1518                 -- interface we have sucked in.
1519                 --
1520                 -- What /is/ in the PIT is:
1521                 --
1522                 -- * The Module
1523                 --
1524                 -- * Fingerprint info
1525                 --
1526                 -- * Its exports
1527                 --
1528                 -- * Fixities
1529                 --
1530                 -- * Deprecations and warnings
1531
1532         eps_PTE :: !PackageTypeEnv,        
1533                 -- ^ Result of typechecking all the external package
1534                 -- interface files we have sucked in. The domain of
1535                 -- the mapping is external-package modules
1536                 
1537         eps_inst_env     :: !PackageInstEnv,   -- ^ The total 'InstEnv' accumulated
1538                                                -- from all the external-package modules
1539         eps_fam_inst_env :: !PackageFamInstEnv,-- ^ The total 'FamInstEnv' accumulated
1540                                                -- from all the external-package modules
1541         eps_rule_base    :: !PackageRuleBase,  -- ^ The total 'RuleEnv' accumulated
1542                                                -- from all the external-package modules
1543         eps_vect_info    :: !PackageVectInfo,  -- ^ The total 'VectInfo' accumulated
1544                                                -- from all the external-package modules
1545         eps_ann_env      :: !PackageAnnEnv,    -- ^ The total 'AnnEnv' accumulated
1546                                                -- from all the external-package modules
1547
1548         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- ^ The family instances accumulated from external
1549                                                          -- packages, keyed off the module that declared them
1550
1551         eps_stats :: !EpsStats                 -- ^ Stastics about what was loaded from external packages
1552   }
1553
1554 -- | Accumulated statistics about what we are putting into the 'ExternalPackageState'.
1555 -- \"In\" means stuff that is just /read/ from interface files,
1556 -- \"Out\" means actually sucked in and type-checked
1557 data EpsStats = EpsStats { n_ifaces_in
1558                          , n_decls_in, n_decls_out 
1559                          , n_rules_in, n_rules_out
1560                          , n_insts_in, n_insts_out :: !Int }
1561
1562 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1563 -- ^ Add stats for one newly-read interface
1564 addEpsInStats stats n_decls n_insts n_rules
1565   = stats { n_ifaces_in = n_ifaces_in stats + 1
1566           , n_decls_in  = n_decls_in stats + n_decls
1567           , n_insts_in  = n_insts_in stats + n_insts
1568           , n_rules_in  = n_rules_in stats + n_rules }
1569 \end{code}
1570
1571 Names in a NameCache are always stored as a Global, and have the SrcLoc 
1572 of their binding locations.
1573
1574 Actually that's not quite right.  When we first encounter the original
1575 name, we might not be at its binding site (e.g. we are reading an
1576 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1577 its binding site, we fix it up.
1578
1579 \begin{code}
1580 -- | The NameCache makes sure that there is just one Unique assigned for
1581 -- each original name; i.e. (module-name, occ-name) pair and provides
1582 -- something of a lookup mechanism for those names.
1583 data NameCache
1584  = NameCache {  nsUniqs :: UniqSupply,
1585                 -- ^ Supply of uniques
1586                 nsNames :: OrigNameCache,
1587                 -- ^ Ensures that one original name gets one unique
1588                 nsIPs   :: OrigIParamCache
1589                 -- ^ Ensures that one implicit parameter name gets one unique
1590    }
1591
1592 -- | Per-module cache of original 'OccName's given 'Name's
1593 type OrigNameCache   = ModuleEnv (OccEnv Name)
1594
1595 -- | Module-local cache of implicit parameter 'OccName's given 'Name's
1596 type OrigIParamCache = Map (IPName OccName) (IPName Name)
1597 \end{code}
1598
1599
1600
1601 %************************************************************************
1602 %*                                                                      *
1603                 The module graph and ModSummary type
1604         A ModSummary is a node in the compilation manager's
1605         dependency graph, and it's also passed to hscMain
1606 %*                                                                      *
1607 %************************************************************************
1608
1609 \begin{code}
1610 -- | A ModuleGraph contains all the nodes from the home package (only).
1611 -- There will be a node for each source module, plus a node for each hi-boot
1612 -- module.
1613 --
1614 -- The graph is not necessarily stored in topologically-sorted order.  Use
1615 -- 'GHC.topSortModuleGraph' and 'Digraph.flattenSCC' to achieve this.
1616 type ModuleGraph = [ModSummary]
1617
1618 emptyMG :: ModuleGraph
1619 emptyMG = []
1620
1621 -- | A single node in a 'ModuleGraph. The nodes of the module graph are one of:
1622 --
1623 -- * A regular Haskell source module
1624 --
1625 -- * A hi-boot source module
1626 --
1627 -- * An external-core source module
1628 data ModSummary
1629    = ModSummary {
1630         ms_mod       :: Module,                 -- ^ Identity of the module
1631         ms_hsc_src   :: HscSource,              -- ^ The module source either plain Haskell, hs-boot or external core
1632         ms_location  :: ModLocation,            -- ^ Location of the various files belonging to the module
1633         ms_hs_date   :: ClockTime,              -- ^ Timestamp of source file
1634         ms_obj_date  :: Maybe ClockTime,        -- ^ Timestamp of object, if we have one
1635         ms_srcimps   :: [Located (ImportDecl RdrName)], -- ^ Source imports of the module
1636         ms_imps      :: [Located (ImportDecl RdrName)], -- ^ Non-source imports of the module
1637         ms_hspp_file :: FilePath,               -- ^ Filename of preprocessed source file
1638         ms_hspp_opts :: DynFlags,               -- ^ Cached flags from @OPTIONS@, @INCLUDE@
1639                                                 -- and @LANGUAGE@ pragmas in the modules source code
1640         ms_hspp_buf  :: Maybe StringBuffer      -- ^ The actual preprocessed source, if we have it
1641      }
1642
1643 ms_mod_name :: ModSummary -> ModuleName
1644 ms_mod_name = moduleName . ms_mod
1645
1646 -- The ModLocation contains both the original source filename and the
1647 -- filename of the cleaned-up source file after all preprocessing has been
1648 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1649 -- all files anyway, and there's no point in doing this twice -- just 
1650 -- park the result in a temp file, put the name of it in the location,
1651 -- and let @compile@ read from that file on the way back up.
1652
1653 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1654 -- the ms_hs_date and imports can, of course, change
1655
1656 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1657 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1658 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1659 msObjFilePath ms = ml_obj_file (ms_location ms)
1660
1661 -- | Did this 'ModSummary' originate from a hs-boot file?
1662 isBootSummary :: ModSummary -> Bool
1663 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1664
1665 instance Outputable ModSummary where
1666    ppr ms
1667       = sep [text "ModSummary {",
1668              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1669                           text "ms_mod =" <+> ppr (ms_mod ms) 
1670                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1671                           text "ms_imps =" <+> ppr (ms_imps ms),
1672                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1673              char '}'
1674             ]
1675
1676 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1677 showModMsg target recomp mod_summary
1678   = showSDoc $
1679         hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1680               char '(', text (normalise $ msHsFilePath mod_summary) <> comma,
1681               case target of
1682                   HscInterpreted | recomp 
1683                              -> text "interpreted"
1684                   HscNothing -> text "nothing"
1685                   _          -> text (normalise $ msObjFilePath mod_summary),
1686               char ')']
1687  where 
1688     mod     = moduleName (ms_mod mod_summary)
1689     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1690 \end{code}
1691
1692
1693 %************************************************************************
1694 %*                                                                      *
1695 \subsection{Hpc Support}
1696 %*                                                                      *
1697 %************************************************************************
1698
1699 \begin{code}
1700 -- | Information about a modules use of Haskell Program Coverage
1701 data HpcInfo
1702   = HpcInfo 
1703      { hpcInfoTickCount :: Int
1704      , hpcInfoHash      :: Int
1705      }
1706   | NoHpcInfo 
1707      { hpcUsed          :: AnyHpcUsage  -- ^ Is hpc used anywhere on the module \*tree\*?
1708      }
1709
1710 -- | This is used to signal if one of my imports used HPC instrumentation
1711 -- even if there is no module-local HPC usage
1712 type AnyHpcUsage = Bool
1713
1714 emptyHpcInfo :: AnyHpcUsage -> HpcInfo
1715 emptyHpcInfo = NoHpcInfo 
1716
1717 -- | Find out if HPC is used by this module or any of the modules
1718 -- it depends upon
1719 isHpcUsed :: HpcInfo -> AnyHpcUsage
1720 isHpcUsed (HpcInfo {})                   = True
1721 isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
1722 \end{code}
1723
1724 %************************************************************************
1725 %*                                                                      *
1726 \subsection{Vectorisation Support}
1727 %*                                                                      *
1728 %************************************************************************
1729
1730 The following information is generated and consumed by the vectorisation
1731 subsystem.  It communicates the vectorisation status of declarations from one
1732 module to another.
1733
1734 Why do we need both f and f_v in the ModGuts/ModDetails/EPS version VectInfo
1735 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1736 vectorisation, we need to know `f_v', whose `Var' we cannot lookup based
1737 on just the OccName easily in a Core pass.
1738
1739 \begin{code}
1740 -- | Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'.
1741 data VectInfo      
1742   = VectInfo {
1743       vectInfoVar     :: VarEnv  (Var    , Var  ),   -- ^ @(f, f_v)@ keyed on @f@
1744       vectInfoTyCon   :: NameEnv (TyCon  , TyCon),   -- ^ @(T, T_v)@ keyed on @T@
1745       vectInfoDataCon :: NameEnv (DataCon, DataCon), -- ^ @(C, C_v)@ keyed on @C@
1746       vectInfoPADFun  :: NameEnv (TyCon  , Var),     -- ^ @(T_v, paT)@ keyed on @T_v@
1747       vectInfoIso     :: NameEnv (TyCon  , Var)      -- ^ @(T, isoT)@ keyed on @T@
1748     }
1749
1750 -- | Vectorisation information for 'ModIface': a slightly less low-level view
1751 data IfaceVectInfo 
1752   = IfaceVectInfo {
1753       ifaceVectInfoVar        :: [Name],
1754         -- ^ All variables in here have a vectorised variant
1755       ifaceVectInfoTyCon      :: [Name],
1756         -- ^ All 'TyCon's in here have a vectorised variant;
1757         -- the name of the vectorised variant and those of its
1758         -- data constructors are determined by 'OccName.mkVectTyConOcc'
1759         -- and 'OccName.mkVectDataConOcc'; the names of
1760         -- the isomorphisms are determined by 'OccName.mkVectIsoOcc'
1761       ifaceVectInfoTyConReuse :: [Name]              
1762         -- ^ The vectorised form of all the 'TyCon's in here coincides with
1763         -- the unconverted form; the name of the isomorphisms is determined
1764         -- by 'OccName.mkVectIsoOcc'
1765     }
1766
1767 noVectInfo :: VectInfo
1768 noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyNameEnv
1769
1770 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1771 plusVectInfo vi1 vi2 = 
1772   VectInfo (vectInfoVar     vi1 `plusVarEnv`  vectInfoVar     vi2)
1773            (vectInfoTyCon   vi1 `plusNameEnv` vectInfoTyCon   vi2)
1774            (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
1775            (vectInfoPADFun  vi1 `plusNameEnv` vectInfoPADFun  vi2)
1776            (vectInfoIso     vi1 `plusNameEnv` vectInfoIso     vi2)
1777
1778 concatVectInfo :: [VectInfo] -> VectInfo
1779 concatVectInfo = foldr plusVectInfo noVectInfo
1780
1781 noIfaceVectInfo :: IfaceVectInfo
1782 noIfaceVectInfo = IfaceVectInfo [] [] []
1783 \end{code}
1784
1785 %************************************************************************
1786 %*                                                                      *
1787 \subsection{Linkable stuff}
1788 %*                                                                      *
1789 %************************************************************************
1790
1791 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1792 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1793
1794 \begin{code}
1795 -- | Information we can use to dynamically link modules into the compiler
1796 data Linkable = LM {
1797   linkableTime     :: ClockTime,        -- ^ Time at which this linkable was built
1798                                         -- (i.e. when the bytecodes were produced,
1799                                         --       or the mod date on the files)
1800   linkableModule   :: Module,           -- ^ The linkable module itself
1801   linkableUnlinked :: [Unlinked]
1802     -- ^ Those files and chunks of code we have yet to link.
1803     --
1804     -- INVARIANT: A valid linkable always has at least one 'Unlinked' item.
1805     -- If this list is empty, the Linkable represents a fake linkable, which
1806     -- is generated in HscNothing mode to avoid recompiling modules.
1807     --
1808     -- XXX: Do items get removed from this list when they get linked?
1809  }
1810
1811 isObjectLinkable :: Linkable -> Bool
1812 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1813   where unlinked = linkableUnlinked l
1814         -- A linkable with no Unlinked's is treated as a BCO.  We can
1815         -- generate a linkable with no Unlinked's as a result of
1816         -- compiling a module in HscNothing mode, and this choice
1817         -- happens to work well with checkStability in module GHC.
1818
1819 linkableObjs :: Linkable -> [FilePath]
1820 linkableObjs l = [ f | DotO f <- linkableUnlinked l ]
1821
1822 instance Outputable Linkable where
1823    ppr (LM when_made mod unlinkeds)
1824       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1825         $$ nest 3 (ppr unlinkeds)
1826
1827 -------------------------------------------
1828
1829 -- | Objects which have yet to be linked by the compiler
1830 data Unlinked
1831    = DotO FilePath      -- ^ An object file (.o)
1832    | DotA FilePath      -- ^ Static archive file (.a)
1833    | DotDLL FilePath    -- ^ Dynamically linked library file (.so, .dll, .dylib)
1834    | BCOs CompiledByteCode ModBreaks    -- ^ A byte-code object, lives only in memory
1835
1836 #ifndef GHCI
1837 data CompiledByteCode = CompiledByteCodeUndefined
1838 _unused :: CompiledByteCode
1839 _unused = CompiledByteCodeUndefined
1840 #endif
1841
1842 instance Outputable Unlinked where
1843    ppr (DotO path)   = text "DotO" <+> text path
1844    ppr (DotA path)   = text "DotA" <+> text path
1845    ppr (DotDLL path) = text "DotDLL" <+> text path
1846 #ifdef GHCI
1847    ppr (BCOs bcos _) = text "BCOs" <+> ppr bcos
1848 #else
1849    ppr (BCOs _ _)    = text "No byte code"
1850 #endif
1851
1852 -- | Is this an actual file on disk we can link in somehow?
1853 isObject :: Unlinked -> Bool
1854 isObject (DotO _)   = True
1855 isObject (DotA _)   = True
1856 isObject (DotDLL _) = True
1857 isObject _          = False
1858
1859 -- | Is this a bytecode linkable with no file on disk?
1860 isInterpretable :: Unlinked -> Bool
1861 isInterpretable = not . isObject
1862
1863 -- | Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
1864 nameOfObject :: Unlinked -> FilePath
1865 nameOfObject (DotO fn)   = fn
1866 nameOfObject (DotA fn)   = fn
1867 nameOfObject (DotDLL fn) = fn
1868 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1869
1870 -- | Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
1871 byteCodeOfObject :: Unlinked -> CompiledByteCode
1872 byteCodeOfObject (BCOs bc _) = bc
1873 byteCodeOfObject other       = pprPanic "byteCodeOfObject" (ppr other)
1874 \end{code}
1875
1876 %************************************************************************
1877 %*                                                                      *
1878 \subsection{Breakpoint Support}
1879 %*                                                                      *
1880 %************************************************************************
1881
1882 \begin{code}
1883 -- | Breakpoint index
1884 type BreakIndex = Int
1885
1886 -- | All the information about the breakpoints for a given module
1887 data ModBreaks
1888    = ModBreaks
1889    { modBreaks_flags :: BreakArray
1890         -- ^ The array of flags, one per breakpoint, 
1891         -- indicating which breakpoints are enabled.
1892    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
1893         -- ^ An array giving the source span of each breakpoint.
1894    , modBreaks_vars :: !(Array BreakIndex [OccName])
1895         -- ^ An array giving the names of the free variables at each breakpoint.
1896    , modBreaks_decls :: !(Array BreakIndex [String])
1897         -- ^ An array giving the names of the declarations enclosing each breakpoint.
1898    }
1899
1900 emptyModBreaks :: ModBreaks
1901 emptyModBreaks = ModBreaks
1902    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
1903          -- Todo: can we avoid this? 
1904    , modBreaks_locs  = array (0,-1) []
1905    , modBreaks_vars  = array (0,-1) []
1906    , modBreaks_decls = array (0,-1) []
1907    }
1908 \end{code}