[project @ 2005-04-13 13:17:35 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
1
2 % (c) The University of Glasgow, 2000
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 module HscTypes ( 
8         -- * Sessions and compilation state
9         Session(..), HscEnv(..), hscEPS,
10         FinderCache, FinderCacheEntry,
11         Target(..), TargetId(..), pprTarget, pprTargetId,
12         ModuleGraph, emptyMG,
13
14         ModDetails(..), emptyModDetails,
15         ModGuts(..), ModImports(..), ForeignStubs(..),
16
17         ModSummary(..), showModMsg, isBootSummary,
18         msHsFilePath, msHiFilePath, msObjFilePath, 
19
20         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
21         
22         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
23         hptInstances, hptRules,
24
25         ExternalPackageState(..), EpsStats(..), addEpsInStats,
26         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
27         lookupIface, lookupIfaceByModule, emptyModIface,
28
29         InteractiveContext(..), emptyInteractiveContext, 
30         icPrintUnqual, unQualInScope,
31
32         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
33         emptyIfaceDepCache, 
34
35         Deprecs(..), IfaceDeprecs,
36
37         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
38
39         implicitTyThings, 
40
41         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
42         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
43         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
44         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
45
46         WhetherHasOrphans, IsBootInterface, Usage(..), 
47         Dependencies(..), noDependencies,
48         InstPool, Gated, addInstsToPool, 
49         RulePool, addRulesToPool, 
50         NameCache(..), OrigNameCache, OrigIParamCache,
51         Avails, availsToNameSet, availName, availNames,
52         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
53         IfaceExport,
54
55         Deprecations, DeprecTxt, lookupDeprec, plusDeprecs,
56
57         InstEnv, DFunId,
58         PackageInstEnv, PackageRuleBase,
59
60         -- Linker stuff
61         Linkable(..), isObjectLinkable,
62         Unlinked(..), CompiledByteCode,
63         isObject, nameOfObject, isInterpretable, byteCodeOfObject
64     ) where
65
66 #include "HsVersions.h"
67
68 #ifdef GHCI
69 import ByteCodeAsm      ( CompiledByteCode )
70 #endif
71
72 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv,
73                           LocalRdrEnv, emptyLocalRdrEnv,
74                           GlobalRdrElt(..), mkRdrUnqual, lookupGRE_RdrName )
75 import Name             ( Name, NamedThing, getName, nameOccName, nameModule )
76 import NameEnv
77 import NameSet  
78 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
79                           extendOccEnv )
80 import Module
81 import InstEnv          ( InstEnv, DFunId )
82 import Rules            ( RuleBase )
83 import CoreSyn          ( CoreBind )
84 import Id               ( Id )
85 import Type             ( TyThing(..) )
86
87 import Class            ( Class, classSelIds, classTyCon )
88 import TyCon            ( TyCon, tyConSelIds, tyConDataCons )
89 import DataCon          ( dataConImplicitIds )
90 import Packages         ( PackageIdH, PackageId, PackageConfig )
91 import DynFlags         ( DynFlags(..), isOneShot )
92 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString )
93 import BasicTypes       ( Version, initialVersion, IPName, 
94                           Fixity, defaultFixity, DeprecTxt )
95
96 import IfaceSyn         ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
97
98 import FiniteMap        ( FiniteMap )
99 import CoreSyn          ( IdCoreRule )
100 import Maybes           ( orElse, fromJust, expectJust )
101 import Outputable
102 import SrcLoc           ( SrcSpan )
103 import UniqSupply       ( UniqSupply )
104 import FastString       ( FastString )
105
106 import DATA_IOREF       ( IORef, readIORef )
107 import StringBuffer     ( StringBuffer )
108 import Time             ( ClockTime )
109 \end{code}
110
111
112 %************************************************************************
113 %*                                                                      *
114 \subsection{Compilation environment}
115 %*                                                                      *
116 %************************************************************************
117
118
119 \begin{code}
120 -- | The Session is a handle to the complete state of a compilation
121 -- session.  A compilation session consists of a set of modules
122 -- constituting the current program or library, the context for
123 -- interactive evaluation, and various caches.
124 newtype Session = Session (IORef HscEnv)
125 \end{code}
126
127 HscEnv is like Session, except that some of the fields are immutable.
128 An HscEnv is used to compile a single module from plain Haskell source
129 code (after preprocessing) to either C, assembly or C--.  Things like
130 the module graph don't change during a single compilation.
131
132 Historical note: "hsc" used to be the name of the compiler binary,
133 when there was a separate driver and compiler.  To compile a single
134 module, the driver would invoke hsc on the source code... so nowadays
135 we think of hsc as the layer of the compiler that deals with compiling
136 a single module.
137
138 \begin{code}
139 data HscEnv 
140   = HscEnv { 
141         hsc_dflags :: DynFlags,
142                 -- The dynamic flag settings
143
144         hsc_targets :: [Target],
145                 -- The targets (or roots) of the current session
146
147         hsc_mod_graph :: ModuleGraph,
148                 -- The module graph of the current session
149
150         hsc_IC :: InteractiveContext,
151                 -- The context for evaluating interactive statements
152
153         hsc_HPT    :: HomePackageTable,
154                 -- The home package table describes already-compiled
155                 -- home-packge modules, *excluding* the module we 
156                 -- are compiling right now.
157                 -- (In one-shot mode the current module is the only
158                 --  home-package module, so hsc_HPT is empty.  All other
159                 --  modules count as "external-package" modules.
160                 --  However, even in GHCi mode, hi-boot interfaces are
161                 --  demand-loadeded into the external-package table.)
162                 --
163                 -- hsc_HPT is not mutable because we only demand-load 
164                 -- external packages; the home package is eagerly 
165                 -- loaded, module by module, by the compilation manager.
166                 --      
167                 -- The HPT may contain modules compiled earlier by --make
168                 -- but not actually below the current module in the dependency
169                 -- graph.  (This changes a previous invariant: changed Jan 05.)
170         
171         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
172         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
173                 -- These are side-effected by compiling to reflect
174                 -- sucking in interface files.  They cache the state of
175                 -- external interface files, in effect.
176
177         hsc_FC  :: {-# UNPACK #-} !(IORef FinderCache)
178                 -- The finder's cache.  This caches the location of modules,
179                 -- so we don't have to search the filesystem multiple times.
180  }
181
182 hscEPS :: HscEnv -> IO ExternalPackageState
183 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
184
185 -- | A compilation target.
186 --
187 -- A target may be supplied with the actual text of the
188 -- module.  If so, use this instead of the file contents (this
189 -- is for use in an IDE where the file hasn't been saved by
190 -- the user yet).
191 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
192
193 data TargetId
194   = TargetModule Module    -- ^ A module name: search for the file
195   | TargetFile   FilePath  -- ^ A filename: parse it to find the module name.
196   deriving Eq
197
198 pprTarget :: Target -> SDoc
199 pprTarget (Target id _) = pprTargetId id
200
201 pprTargetId (TargetModule m) = ppr m
202 pprTargetId (TargetFile f)   = text f
203
204 type FinderCache = ModuleEnv FinderCacheEntry
205 type FinderCacheEntry = (ModLocation, Maybe (PackageConfig,Bool))
206         -- The finder's cache (see module Finder)
207
208 type HomePackageTable  = ModuleEnv HomeModInfo
209         -- Domain = modules in the home package
210 type PackageIfaceTable = ModuleEnv ModIface
211         -- Domain = modules in the imported packages
212
213 emptyHomePackageTable  = emptyModuleEnv
214 emptyPackageIfaceTable = emptyModuleEnv
215
216 data HomeModInfo 
217   = HomeModInfo { hm_iface    :: !ModIface,
218                   hm_details  :: !ModDetails,
219                   hm_linkable :: !(Maybe Linkable) }
220                 -- hm_linkable might be Nothing if:
221                 --   a) this is an .hs-boot module
222                 --   b) temporarily during compilation if we pruned away
223                 --      the old linkable because it was out of date.
224                 -- after a complete compilation (GHC.load), all hm_linkable
225                 -- fields in the HPT will be Just.
226 \end{code}
227
228 Simple lookups in the symbol table.
229
230 \begin{code}
231 lookupIface :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
232 -- We often have two IfaceTables, and want to do a lookup
233 lookupIface hpt pit mod
234   = case lookupModuleEnv hpt mod of
235         Just mod_info -> Just (hm_iface mod_info)
236         Nothing       -> lookupModuleEnv pit mod
237
238 lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
239 -- We often have two IfaceTables, and want to do a lookup
240 lookupIfaceByModule hpt pit mod
241   = case lookupModuleEnv hpt mod of
242         Just mod_info -> Just (hm_iface mod_info)
243         Nothing       -> lookupModuleEnv pit mod
244 \end{code}
245
246
247 \begin{code}
248 hptInstances :: HscEnv -> (Module -> Bool) -> [DFunId]
249 -- Find all the instance declarations that are in modules imported 
250 -- by this one, directly or indirectly, and are in the Home Package Table
251 -- This ensures that we don't see instances from modules --make compiled 
252 -- before this one, but which are not below this one
253 hptInstances hsc_env want_this_module
254   = [ dfun 
255     | mod_info <- moduleEnvElts (hsc_HPT hsc_env)
256     , want_this_module (mi_module (hm_iface mod_info))
257     , dfun <- md_insts (hm_details mod_info) ]
258
259 hptRules :: HscEnv -> [(Module, IsBootInterface)] -> [IdCoreRule]
260 -- Get rules from modules "below" this one (in the dependency sense)
261 -- C.f Inst.hptInstances
262 hptRules hsc_env deps
263   | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
264   | otherwise
265   = let 
266         hpt = hsc_HPT hsc_env
267     in
268     [ rule
269     |   -- Find each non-hi-boot module below me
270       (mod, False) <- deps
271
272         -- Look it up in the HPT
273     , let mod_info = ASSERT( mod `elemModuleEnv` hpt )
274                      fromJust (lookupModuleEnv hpt mod)
275
276         -- And get its dfuns
277     , rule <- md_rules (hm_details mod_info) ]
278 \end{code}
279
280
281 %************************************************************************
282 %*                                                                      *
283 \subsection{Symbol tables and Module details}
284 %*                                                                      *
285 %************************************************************************
286
287 A @ModIface@ plus a @ModDetails@ summarises everything we know 
288 about a compiled module.  The @ModIface@ is the stuff *before* linking,
289 and can be written out to an interface file.  (The @ModDetails@ is after 
290 linking; it is the "linked" form of the mi_decls field.)
291
292 When we *read* an interface file, we also construct a @ModIface@ from it,
293 except that the mi_decls part is empty; when reading we consolidate
294 the declarations into a single indexed map in the @PersistentRenamerState@.
295
296 \begin{code}
297 data ModIface 
298    = ModIface {
299         mi_package  :: !PackageIdH,         -- Which package the module comes from
300         mi_module   :: !Module,
301         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
302
303         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
304         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
305
306         mi_deps     :: Dependencies,
307                 -- This is consulted for directly-imported modules,
308                 -- but not for anything else (hence lazy)
309
310                 -- Usages; kept sorted so that it's easy to decide
311                 -- whether to write a new iface file (changing usages
312                 -- doesn't affect the version of this module)
313         mi_usages   :: [Usage],
314                 -- NOT STRICT!  we read this field lazily from the interface file
315                 -- It is *only* consulted by the recompilation checker
316
317                 -- Exports
318                 -- Kept sorted by (mod,occ), to make version comparisons easier
319         mi_exports  :: ![IfaceExport],
320         mi_exp_vers :: !Version,        -- Version number of export list
321
322                 -- Fixities
323         mi_fixities :: [(OccName,Fixity)],
324                 -- NOT STRICT!  we read this field lazily from the interface file
325
326                 -- Deprecations
327         mi_deprecs  :: IfaceDeprecs,
328                 -- NOT STRICT!  we read this field lazily from the interface file
329
330                 -- Type, class and variable declarations
331                 -- The version of an Id changes if its fixity or deprecations change
332                 --      (as well as its type of course)
333                 -- Ditto data constructors, class operations, except that 
334                 -- the version of the parent class/tycon changes
335         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
336
337         mi_globals  :: !(Maybe GlobalRdrEnv),
338                 -- Its top level environment or Nothing if we read this
339                 -- interface from an interface file.  (We need the source
340                 -- file to figure out the top-level environment.)
341
342                 -- Instance declarations and rules
343         mi_insts     :: [IfaceInst],    -- Sorted
344         mi_rules     :: [IfaceRule],    -- Sorted
345         mi_rule_vers :: !Version,       -- Version number for rules and instances combined
346
347                 -- Cached environments for easy lookup
348                 -- These are computed (lazily) from other fields
349                 -- and are not put into the interface file
350         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
351         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
352         mi_ver_fn  :: OccName -> Maybe Version  -- Cached lookup for mi_decls
353                         -- The Nothing in mi_ver_fn means that the thing
354                         -- isn't in decls. It's useful to know that when
355                         -- seeing if we are up to date wrt the old interface
356      }
357
358 -- Should be able to construct ModDetails from mi_decls in ModIface
359 data ModDetails
360    = ModDetails {
361         -- The next three fields are created by the typechecker
362         md_types    :: !TypeEnv,
363         md_exports  :: NameSet,
364         md_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
365         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
366      }
367
368 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
369                                md_exports = emptyNameSet,
370                                md_insts = [],
371                                md_rules = [] }
372
373 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
374 -- There is only one ModGuts at any time, the one for the module
375 -- being compiled right now.  Once it is compiled, a ModIface and 
376 -- ModDetails are extracted and the ModGuts is dicarded.
377
378 data ModGuts
379   = ModGuts {
380         mg_module   :: !Module,
381         mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
382         mg_exports  :: !NameSet,        -- What it exports
383         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
384         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
385                                         --      generate initialisation code
386         mg_usages   :: ![Usage],        -- Version info for what it needed
387
388         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
389         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
390         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
391
392         mg_types    :: !TypeEnv,
393         mg_insts    :: ![DFunId],       -- Instances 
394         mg_rules    :: ![IdCoreRule],   -- Rules from this module
395         mg_binds    :: ![CoreBind],     -- Bindings for this module
396         mg_foreign  :: !ForeignStubs
397     }
398
399 -- The ModGuts takes on several slightly different forms:
400 --
401 -- After simplification, the following fields change slightly:
402 --      mg_rules        Orphan rules only (local ones now attached to binds)
403 --      mg_binds        With rules attached
404 --
405 -- After CoreTidy, the following fields change slightly:
406 --      mg_types        Now contains Ids as well, replete with final IdInfo
407 --                         The Ids are only the ones that are visible from
408 --                         importing modules.  Without -O that means only
409 --                         exported Ids, but with -O importing modules may
410 --                         see ids mentioned in unfoldings of exported Ids
411 --
412 --      mg_insts        Same DFunIds as before, but with final IdInfo,
413 --                         and the unique might have changed; remember that
414 --                         CoreTidy links up the uniques of old and new versions
415 --
416 --      mg_rules        All rules for exported things, substituted with final Ids
417 --
418 --      mg_binds        Tidied
419
420
421
422 data ModImports
423   = ModImports {
424         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
425                                                 -- Boolean is true if we imported the whole
426                                                 --      module (apart, perhaps, from hiding some)
427         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
428                                                 --      directly or indirectly
429         imp_home_names :: !NameSet              -- Home package things on which we depend,
430                                                 --      directly or indirectly
431     }
432
433 data ForeignStubs = NoStubs
434                   | ForeignStubs
435                         SDoc            -- Header file prototypes for
436                                         --      "foreign exported" functions
437                         SDoc            -- C stubs to use when calling
438                                         --      "foreign exported" functions
439                         [FastString]    -- Headers that need to be included
440                                         --      into C code generated for this module
441                         [Id]            -- Foreign-exported binders
442                                         --      we have to generate code to register these
443
444 \end{code}
445
446 \begin{code}
447 emptyModIface :: PackageIdH -> Module -> ModIface
448 emptyModIface pkg mod
449   = ModIface { mi_package  = pkg,
450                mi_module   = mod,
451                mi_mod_vers = initialVersion,
452                mi_orphan   = False,
453                mi_boot     = False,
454                mi_deps     = noDependencies,
455                mi_usages   = [],
456                mi_exports  = [],
457                mi_exp_vers = initialVersion,
458                mi_fixities = [],
459                mi_deprecs  = NoDeprecs,
460                mi_insts = [],
461                mi_rules = [],
462                mi_decls = [],
463                mi_globals  = Nothing,
464                mi_rule_vers = initialVersion,
465                mi_dep_fn = emptyIfaceDepCache,
466                mi_fix_fn = emptyIfaceFixCache,
467                mi_ver_fn = emptyIfaceVerCache
468     }           
469 \end{code}
470
471
472 %************************************************************************
473 %*                                                                      *
474 \subsection{The interactive context}
475 %*                                                                      *
476 %************************************************************************
477
478 \begin{code}
479 data InteractiveContext 
480   = InteractiveContext { 
481         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
482                                         -- these modules
483
484         ic_exports :: [Module],         -- Include just the exports of these
485                                         -- modules
486
487         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
488                                         -- ic_toplev_scope and ic_exports
489
490         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
491                                         -- during interaction
492
493         ic_type_env :: TypeEnv          -- Ditto for types
494     }
495
496 emptyInteractiveContext
497   = InteractiveContext { ic_toplev_scope = [],
498                          ic_exports = [],
499                          ic_rn_gbl_env = emptyGlobalRdrEnv,
500                          ic_rn_local_env = emptyLocalRdrEnv,
501                          ic_type_env = emptyTypeEnv }
502
503 icPrintUnqual :: InteractiveContext -> PrintUnqualified
504 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
505 \end{code}
506
507 @unQualInScope@ returns a function that takes a @Name@ and tells whether
508 its unqualified name is in scope.  This is put as a boolean flag in
509 the @Name@'s provenance to guide whether or not to print the name qualified
510 in error messages.
511
512 \begin{code}
513 unQualInScope :: GlobalRdrEnv -> PrintUnqualified
514 -- True if 'f' is in scope, and has only one binding,
515 -- and the thing it is bound to is the name we are looking for
516 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
517 --
518 -- [Out of date] Also checks for built-in syntax, which is always 'in scope'
519 unQualInScope env mod occ
520   = case lookupGRE_RdrName (mkRdrUnqual occ) env of
521         [gre] -> nameModule (gre_name gre) == mod
522         other -> False
523 \end{code}
524
525
526 %************************************************************************
527 %*                                                                      *
528                 TyThing
529 %*                                                                      *
530 %************************************************************************
531
532 \begin{code}
533 implicitTyThings :: TyThing -> [TyThing]
534 implicitTyThings (AnId id)   = []
535
536         -- For type constructors, add the data cons (and their extras),
537         -- and the selectors and generic-programming Ids too
538         --
539         -- Newtypes don't have a worker Id, so don't generate that?
540 implicitTyThings (ATyCon tc) = map AnId (tyConSelIds tc) ++ 
541                                concatMap (extras_plus . ADataCon) (tyConDataCons tc)
542                      
543         -- For classes, add the class TyCon too (and its extras)
544         -- and the class selector Ids
545 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
546                                extras_plus (ATyCon (classTyCon cl))
547                          
548
549         -- For data cons add the worker and wrapper (if any)
550 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
551
552 extras_plus thing = thing : implicitTyThings thing
553
554 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
555 extendTypeEnvWithIds env ids
556   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
557 \end{code}
558
559 %************************************************************************
560 %*                                                                      *
561                 TypeEnv
562 %*                                                                      *
563 %************************************************************************
564
565 \begin{code}
566 type TypeEnv = NameEnv TyThing
567
568 emptyTypeEnv   :: TypeEnv
569 typeEnvElts    :: TypeEnv -> [TyThing]
570 typeEnvClasses :: TypeEnv -> [Class]
571 typeEnvTyCons  :: TypeEnv -> [TyCon]
572 typeEnvIds     :: TypeEnv -> [Id]
573 lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
574
575 emptyTypeEnv       = emptyNameEnv
576 typeEnvElts    env = nameEnvElts env
577 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
578 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
579 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
580
581 mkTypeEnv :: [TyThing] -> TypeEnv
582 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
583                 
584 lookupTypeEnv = lookupNameEnv
585
586 -- Extend the type environment
587 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
588 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
589
590 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
591 extendTypeEnvList env things = foldl extendTypeEnv env things
592 \end{code}
593
594 \begin{code}
595 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
596 lookupType hpt pte name
597   = case lookupModuleEnv hpt (nameModule name) of
598         Just details -> lookupNameEnv (md_types (hm_details details)) name
599         Nothing      -> lookupNameEnv pte name
600 \end{code}
601
602
603 \begin{code}
604 tyThingTyCon (ATyCon tc) = tc
605 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
606
607 tyThingClass (AClass cls) = cls
608 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
609
610 tyThingDataCon (ADataCon dc) = dc
611 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
612
613 tyThingId (AnId id) = id
614 tyThingId other     = pprPanic "tyThingId" (ppr other)
615 \end{code}
616
617 %************************************************************************
618 %*                                                                      *
619 \subsection{Auxiliary types}
620 %*                                                                      *
621 %************************************************************************
622
623 These types are defined here because they are mentioned in ModDetails,
624 but they are mostly elaborated elsewhere
625
626 \begin{code}
627 mkIfaceVerCache :: [(Version,IfaceDecl)] -> OccName -> Maybe Version
628 mkIfaceVerCache pairs 
629   = \occ -> lookupOccEnv env occ
630   where
631     env = foldl add emptyOccEnv pairs
632     add env (v,d) = extendOccEnv env (ifName d) v
633
634 emptyIfaceVerCache :: OccName -> Maybe Version
635 emptyIfaceVerCache occ = Nothing
636
637 ------------------ Deprecations -------------------------
638 data Deprecs a
639   = NoDeprecs
640   | DeprecAll DeprecTxt -- Whole module deprecated
641   | DeprecSome a        -- Some specific things deprecated
642   deriving( Eq )
643
644 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
645 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
646
647 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
648 mkIfaceDepCache NoDeprecs         = \n -> Nothing
649 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
650 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
651
652 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
653 emptyIfaceDepCache n = Nothing
654
655 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
656 lookupDeprec NoDeprecs        name = Nothing
657 lookupDeprec (DeprecAll  txt) name = Just txt
658 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
659                                             Just (_, txt) -> Just txt
660                                             Nothing       -> Nothing
661
662 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
663 plusDeprecs d NoDeprecs = d
664 plusDeprecs NoDeprecs d = d
665 plusDeprecs d (DeprecAll t) = DeprecAll t
666 plusDeprecs (DeprecAll t) d = DeprecAll t
667 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
668 \end{code}
669
670
671 \begin{code}
672 type Avails       = [AvailInfo]
673 type AvailInfo    = GenAvailInfo Name
674 type RdrAvailInfo = GenAvailInfo OccName
675
676 data GenAvailInfo name  = Avail name     -- An ordinary identifier
677                         | AvailTC name   -- The name of the type or class
678                                   [name] -- The available pieces of type/class.
679                                          -- NB: If the type or class is itself
680                                          -- to be in scope, it must be in this list.
681                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
682                         deriving( Eq )
683                         -- Equality used when deciding if the interface has changed
684
685 type IfaceExport = (Module, [GenAvailInfo OccName])
686
687 availsToNameSet :: [AvailInfo] -> NameSet
688 availsToNameSet avails = foldl add emptyNameSet avails
689                        where
690                          add set avail = addListToNameSet set (availNames avail)
691
692 availName :: GenAvailInfo name -> name
693 availName (Avail n)     = n
694 availName (AvailTC n _) = n
695
696 availNames :: GenAvailInfo name -> [name]
697 availNames (Avail n)      = [n]
698 availNames (AvailTC n ns) = ns
699
700 instance Outputable n => Outputable (GenAvailInfo n) where
701    ppr = pprAvail
702
703 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
704 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
705                                         []  -> empty
706                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
707
708 pprAvail (Avail n) = ppr n
709 \end{code}
710
711 \begin{code}
712 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
713 mkIfaceFixCache pairs 
714   = \n -> lookupOccEnv env n `orElse` defaultFixity
715   where
716    env = mkOccEnv pairs
717
718 emptyIfaceFixCache :: OccName -> Fixity
719 emptyIfaceFixCache n = defaultFixity
720
721 -- This fixity environment is for source code only
722 type FixityEnv = NameEnv FixItem
723
724 -- We keep the OccName in the range so that we can generate an interface from it
725 data FixItem = FixItem OccName Fixity SrcSpan
726
727 instance Outputable FixItem where
728   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
729
730 emptyFixityEnv :: FixityEnv
731 emptyFixityEnv = emptyNameEnv
732
733 lookupFixity :: FixityEnv -> Name -> Fixity
734 lookupFixity env n = case lookupNameEnv env n of
735                         Just (FixItem _ fix _) -> fix
736                         Nothing                -> defaultFixity
737 \end{code}
738
739
740 %************************************************************************
741 %*                                                                      *
742 \subsection{WhatsImported}
743 %*                                                                      *
744 %************************************************************************
745
746 \begin{code}
747 type WhetherHasOrphans   = Bool
748         -- An "orphan" is 
749         --      * an instance decl in a module other than the defn module for 
750         --              one of the tycons or classes in the instance head
751         --      * a transformation rule in a module other than the one defining
752         --              the function in the head of the rule.
753
754 type IsBootInterface = Bool
755
756 -- Dependency info about modules and packages below this one
757 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
758 --
759 -- Invariant: the dependencies of a module M never includes M
760 -- Invariant: the lists are unordered, with no duplicates
761 data Dependencies
762   = Deps { dep_mods  :: [(Module,IsBootInterface)],     -- Home-package module dependencies
763            dep_pkgs  :: [PackageId],                    -- External package dependencies
764            dep_orphs :: [Module] }                      -- Orphan modules (whether home or external pkg)
765   deriving( Eq )
766         -- Equality used only for old/new comparison in MkIface.addVersionInfo
767
768 noDependencies :: Dependencies
769 noDependencies = Deps [] [] []
770           
771 data Usage
772   = Usage { usg_name     :: Module,                     -- Name of the module
773             usg_mod      :: Version,                    -- Module version
774             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
775             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
776             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
777                                                         -- modules this will always be initialVersion)
778     }       deriving( Eq )
779         -- This type doesn't let you say "I imported f but none of the rules in
780         -- the module". If you use anything in the module you get its rule version
781         -- So if the rules change, you'll recompile, even if you don't use them.
782         -- This is easy to implement, and it's safer: you might not have used the rules last
783         -- time round, but if someone has added a new rule you might need it this time
784
785         -- The export list field is (Just v) if we depend on the export list:
786         --      i.e. we imported the module without saying exactly what we imported
787         -- We need to recompile if the module exports changes, because we might
788         -- now have a name clash in the importing module.
789 \end{code}
790
791
792 %************************************************************************
793 %*                                                                      *
794                 The External Package State
795 %*                                                                      *
796 %************************************************************************
797
798 \begin{code}
799 type PackageTypeEnv  = TypeEnv
800 type PackageRuleBase = RuleBase
801 type PackageInstEnv  = InstEnv
802
803 data ExternalPackageState
804   = EPS {
805         eps_is_boot :: !(ModuleEnv (Module, IsBootInterface)),
806                 -- In OneShot mode (only), home-package modules accumulate in the
807                 -- external package state, and are sucked in lazily.
808                 -- For these home-pkg modules (only) we need to record which are
809                 -- boot modules.  We set this field after loading all the 
810                 -- explicitly-imported interfaces, but before doing anything else
811                 --
812                 -- The Module part is not necessary, but it's useful for
813                 -- debug prints, and it's convenient because this field comes
814                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
815
816         eps_PIT :: !PackageIfaceTable,
817                 -- The ModuleIFaces for modules in external packages
818                 -- whose interfaces we have opened
819                 -- The declarations in these interface files are held in
820                 -- eps_decls, eps_insts, eps_rules (below), not in the 
821                 -- mi_decls fields of the iPIT.  
822                 -- What _is_ in the iPIT is:
823                 --      * The Module 
824                 --      * Version info
825                 --      * Its exports
826                 --      * Fixities
827                 --      * Deprecations
828
829         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
830
831         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
832                                                 --   all the external-package modules
833         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
834
835
836         -- Holding pens for stuff that has been read in from file,
837         -- but not yet slurped into the renamer
838         eps_insts :: !InstPool,
839                 -- The as-yet un-slurped instance decls
840                 -- Decls move from here to eps_inst_env
841                 -- Each instance is 'gated' by the names that must be 
842                 -- available before this instance decl is needed.
843
844         eps_rules :: !RulePool,
845                 -- The as-yet un-slurped rules
846
847         eps_stats :: !EpsStats
848   }
849
850 -- "In" means read from iface files
851 -- "Out" means actually sucked in and type-checked
852 data EpsStats = EpsStats { n_ifaces_in
853                          , n_decls_in, n_decls_out 
854                          , n_rules_in, n_rules_out
855                          , n_insts_in, n_insts_out :: !Int }
856 \end{code}
857
858 The NameCache makes sure that there is just one Unique assigned for
859 each original name; i.e. (module-name, occ-name) pair.  The Name is
860 always stored as a Global, and has the SrcLoc of its binding location.
861 Actually that's not quite right.  When we first encounter the original
862 name, we might not be at its binding site (e.g. we are reading an
863 interface file); so we give it 'noSrcLoc' then.  Later, when we find
864 its binding site, we fix it up.
865
866 Exactly the same is true of the Module stored in the Name.  When we first
867 encounter the occurrence, we may not know the details of the module, so
868 we just store junk.  Then when we find the binding site, we fix it up.
869
870 \begin{code}
871 data NameCache
872  = NameCache {  nsUniqs :: UniqSupply,
873                 -- Supply of uniques
874                 nsNames :: OrigNameCache,
875                 -- Ensures that one original name gets one unique
876                 nsIPs   :: OrigIParamCache
877                 -- Ensures that one implicit parameter name gets one unique
878    }
879
880 type OrigNameCache   = ModuleEnv (OccEnv Name)
881 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
882 \end{code}
883
884 \begin{code}
885 type Gated d = ([Name], (Module, SDoc, d))
886         -- The [Name] 'gate' the declaration; always non-empty
887         -- Module records which module this decl belongs to
888         -- SDoc records the pathname of the file, or similar err-ctxt info
889
890 type RulePool = [Gated IfaceRule]
891
892 addRulesToPool :: RulePool
893               -> [Gated IfaceRule]
894               -> RulePool
895 addRulesToPool rules new_rules = new_rules ++ rules
896
897 -------------------------
898 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
899 -- Add stats for one newly-read interface
900 addEpsInStats stats n_decls n_insts n_rules
901   = stats { n_ifaces_in = n_ifaces_in stats + 1
902           , n_decls_in  = n_decls_in stats + n_decls
903           , n_insts_in  = n_insts_in stats + n_insts
904           , n_rules_in  = n_rules_in stats + n_rules }
905
906 -------------------------
907 type InstPool = NameEnv [Gated IfaceInst]
908         -- The key of the Pool is the Class
909         -- The Names are the TyCons in the instance head
910         -- For example, suppose this is in an interface file
911         --      instance C T where ...
912         -- We want to slurp this decl if both C and T are "visible" in 
913         -- the importing module.  See "The gating story" in RnIfaces for details.
914
915
916 addInstsToPool :: InstPool -> [(Name, Gated IfaceInst)] -> InstPool
917 addInstsToPool insts new_insts
918   = foldr add insts new_insts
919   where
920     add :: (Name, Gated IfaceInst) -> NameEnv [Gated IfaceInst] -> NameEnv [Gated IfaceInst]
921     add (cls,new_inst) insts = extendNameEnv_C combine insts cls [new_inst]
922         where
923           combine old_insts _ = new_inst : old_insts
924 \end{code}
925
926
927 %************************************************************************
928 %*                                                                      *
929                 The module graph and ModSummary type
930         A ModSummary is a node in the compilation manager's
931         dependency graph, and it's also passed to hscMain
932 %*                                                                      *
933 %************************************************************************
934
935 A ModuleGraph contains all the nodes from the home package (only).  
936 There will be a node for each source module, plus a node for each hi-boot
937 module.
938
939 \begin{code}
940 type ModuleGraph = [ModSummary]  -- The module graph, 
941                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
942
943 emptyMG :: ModuleGraph
944 emptyMG = []
945
946 -- The nodes of the module graph are
947 --      EITHER a regular Haskell source module
948 --      OR     a hi-boot source module
949
950 data ModSummary
951    = ModSummary {
952         ms_mod       :: Module,                 -- Name of the module
953         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
954         ms_location  :: ModLocation,            -- Location
955         ms_hs_date   :: ClockTime,              -- Timestamp of source file
956         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
957         ms_srcimps   :: [Module],               -- Source imports
958         ms_imps      :: [Module],               -- Non-source imports
959         ms_hspp_file :: Maybe FilePath,         -- Filename of preprocessed source,
960                                                 -- once we have preprocessed it.
961         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
962      }
963
964 -- The ModLocation contains both the original source filename and the
965 -- filename of the cleaned-up source file after all preprocessing has been
966 -- done.  The point is that the summariser will have to cpp/unlit/whatever
967 -- all files anyway, and there's no point in doing this twice -- just 
968 -- park the result in a temp file, put the name of it in the location,
969 -- and let @compile@ read from that file on the way back up.
970
971 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
972 -- the ms_hs_date and imports can, of course, change
973
974 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
975 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
976 msHiFilePath  ms = ml_hi_file  (ms_location ms)
977 msObjFilePath ms = ml_obj_file (ms_location ms)
978
979 isBootSummary :: ModSummary -> Bool
980 isBootSummary ms = isHsBoot (ms_hsc_src ms)
981
982 instance Outputable ModSummary where
983    ppr ms
984       = sep [text "ModSummary {",
985              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
986                           text "ms_mod =" <+> ppr (ms_mod ms) 
987                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
988                           text "ms_imps =" <+> ppr (ms_imps ms),
989                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
990              char '}'
991             ]
992
993 showModMsg :: Bool -> ModSummary -> String
994 showModMsg use_object mod_summary
995   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
996                     char '(', text (msHsFilePath mod_summary) <> comma,
997                     if use_object then text (msObjFilePath mod_summary)
998                               else text "interpreted",
999                     char ')'])
1000  where 
1001     mod     = ms_mod mod_summary 
1002     mod_str = moduleUserString mod ++ hscSourceString (ms_hsc_src mod_summary)
1003 \end{code}
1004
1005
1006 %************************************************************************
1007 %*                                                                      *
1008 \subsection{Linkable stuff}
1009 %*                                                                      *
1010 %************************************************************************
1011
1012 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1013 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1014
1015 \begin{code}
1016 data Linkable = LM {
1017   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1018                                         -- (i.e. when the bytecodes were produced,
1019                                         --       or the mod date on the files)
1020   linkableModule   :: Module,           -- Should be Module, but see below
1021   linkableUnlinked :: [Unlinked]
1022  }
1023
1024 isObjectLinkable :: Linkable -> Bool
1025 isObjectLinkable l = all isObject (linkableUnlinked l)
1026
1027 instance Outputable Linkable where
1028    ppr (LM when_made mod unlinkeds)
1029       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1030         $$ nest 3 (ppr unlinkeds)
1031
1032 -------------------------------------------
1033 data Unlinked
1034    = DotO FilePath
1035    | DotA FilePath
1036    | DotDLL FilePath
1037    | BCOs CompiledByteCode
1038
1039 #ifndef GHCI
1040 data CompiledByteCode = NoByteCode
1041 #endif
1042
1043 instance Outputable Unlinked where
1044    ppr (DotO path)   = text "DotO" <+> text path
1045    ppr (DotA path)   = text "DotA" <+> text path
1046    ppr (DotDLL path) = text "DotDLL" <+> text path
1047 #ifdef GHCI
1048    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1049 #else
1050    ppr (BCOs bcos)   = text "No byte code"
1051 #endif
1052
1053 isObject (DotO _)   = True
1054 isObject (DotA _)   = True
1055 isObject (DotDLL _) = True
1056 isObject _          = False
1057
1058 isInterpretable = not . isObject
1059
1060 nameOfObject (DotO fn)   = fn
1061 nameOfObject (DotA fn)   = fn
1062 nameOfObject (DotDLL fn) = fn
1063
1064 byteCodeOfObject (BCOs bc) = bc
1065 \end{code}
1066
1067
1068