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