[project @ 2005-03-31 10:16:33 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
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_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
364         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
365      }
366
367 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
368                                md_insts = [],
369                                md_rules = [] }
370
371 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
372 -- There is only one ModGuts at any time, the one for the module
373 -- being compiled right now.  Once it is compiled, a ModIface and 
374 -- ModDetails are extracted and the ModGuts is dicarded.
375
376 data ModGuts
377   = ModGuts {
378         mg_module   :: !Module,
379         mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
380         mg_exports  :: !NameSet,        -- What it exports
381         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
382         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
383                                         --      generate initialisation code
384         mg_usages   :: ![Usage],        -- Version info for what it needed
385
386         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
387         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
388         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
389
390         mg_types    :: !TypeEnv,
391         mg_insts    :: ![DFunId],       -- Instances 
392         mg_rules    :: ![IdCoreRule],   -- Rules from this module
393         mg_binds    :: ![CoreBind],     -- Bindings for this module
394         mg_foreign  :: !ForeignStubs
395     }
396
397 -- The ModGuts takes on several slightly different forms:
398 --
399 -- After simplification, the following fields change slightly:
400 --      mg_rules        Orphan rules only (local ones now attached to binds)
401 --      mg_binds        With rules attached
402 --
403 -- After CoreTidy, the following fields change slightly:
404 --      mg_types        Now contains Ids as well, replete with final IdInfo
405 --                         The Ids are only the ones that are visible from
406 --                         importing modules.  Without -O that means only
407 --                         exported Ids, but with -O importing modules may
408 --                         see ids mentioned in unfoldings of exported Ids
409 --
410 --      mg_insts        Same DFunIds as before, but with final IdInfo,
411 --                         and the unique might have changed; remember that
412 --                         CoreTidy links up the uniques of old and new versions
413 --
414 --      mg_rules        All rules for exported things, substituted with final Ids
415 --
416 --      mg_binds        Tidied
417
418
419
420 data ModImports
421   = ModImports {
422         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
423                                                 -- Boolean is true if we imported the whole
424                                                 --      module (apart, perhaps, from hiding some)
425         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
426                                                 --      directly or indirectly
427         imp_home_names :: !NameSet              -- Home package things on which we depend,
428                                                 --      directly or indirectly
429     }
430
431 data ForeignStubs = NoStubs
432                   | ForeignStubs
433                         SDoc            -- Header file prototypes for
434                                         --      "foreign exported" functions
435                         SDoc            -- C stubs to use when calling
436                                         --      "foreign exported" functions
437                         [FastString]    -- Headers that need to be included
438                                         --      into C code generated for this module
439                         [Id]            -- Foreign-exported binders
440                                         --      we have to generate code to register these
441
442 \end{code}
443
444 \begin{code}
445 emptyModIface :: PackageIdH -> Module -> ModIface
446 emptyModIface pkg mod
447   = ModIface { mi_package  = pkg,
448                mi_module   = mod,
449                mi_mod_vers = initialVersion,
450                mi_orphan   = False,
451                mi_boot     = False,
452                mi_deps     = noDependencies,
453                mi_usages   = [],
454                mi_exports  = [],
455                mi_exp_vers = initialVersion,
456                mi_fixities = [],
457                mi_deprecs  = NoDeprecs,
458                mi_insts = [],
459                mi_rules = [],
460                mi_decls = [],
461                mi_globals  = Nothing,
462                mi_rule_vers = initialVersion,
463                mi_dep_fn = emptyIfaceDepCache,
464                mi_fix_fn = emptyIfaceFixCache,
465                mi_ver_fn = emptyIfaceVerCache
466     }           
467 \end{code}
468
469
470 %************************************************************************
471 %*                                                                      *
472 \subsection{The interactive context}
473 %*                                                                      *
474 %************************************************************************
475
476 \begin{code}
477 data InteractiveContext 
478   = InteractiveContext { 
479         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
480                                         -- these modules
481
482         ic_exports :: [Module],         -- Include just the exports of these
483                                         -- modules
484
485         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
486                                         -- ic_toplev_scope and ic_exports
487
488         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
489                                         -- during interaction
490
491         ic_type_env :: TypeEnv          -- Ditto for types
492     }
493
494 emptyInteractiveContext
495   = InteractiveContext { ic_toplev_scope = [],
496                          ic_exports = [],
497                          ic_rn_gbl_env = emptyGlobalRdrEnv,
498                          ic_rn_local_env = emptyLocalRdrEnv,
499                          ic_type_env = emptyTypeEnv }
500
501 icPrintUnqual :: InteractiveContext -> PrintUnqualified
502 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
503 \end{code}
504
505 @unQualInScope@ returns a function that takes a @Name@ and tells whether
506 its unqualified name is in scope.  This is put as a boolean flag in
507 the @Name@'s provenance to guide whether or not to print the name qualified
508 in error messages.
509
510 \begin{code}
511 unQualInScope :: GlobalRdrEnv -> PrintUnqualified
512 -- True if 'f' is in scope, and has only one binding,
513 -- and the thing it is bound to is the name we are looking for
514 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
515 --
516 -- [Out of date] Also checks for built-in syntax, which is always 'in scope'
517 unQualInScope env mod occ
518   = case lookupGRE_RdrName (mkRdrUnqual occ) env of
519         [gre] -> nameModule (gre_name gre) == mod
520         other -> False
521 \end{code}
522
523
524 %************************************************************************
525 %*                                                                      *
526                 TyThing
527 %*                                                                      *
528 %************************************************************************
529
530 \begin{code}
531 implicitTyThings :: TyThing -> [TyThing]
532 implicitTyThings (AnId id)   = []
533
534         -- For type constructors, add the data cons (and their extras),
535         -- and the selectors and generic-programming Ids too
536         --
537         -- Newtypes don't have a worker Id, so don't generate that?
538 implicitTyThings (ATyCon tc) = map AnId (tyConSelIds tc) ++ 
539                                concatMap (extras_plus . ADataCon) (tyConDataCons tc)
540                      
541         -- For classes, add the class TyCon too (and its extras)
542         -- and the class selector Ids
543 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
544                                extras_plus (ATyCon (classTyCon cl))
545                          
546
547         -- For data cons add the worker and wrapper (if any)
548 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
549
550 extras_plus thing = thing : implicitTyThings thing
551
552 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
553 extendTypeEnvWithIds env ids
554   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
555 \end{code}
556
557 %************************************************************************
558 %*                                                                      *
559                 TypeEnv
560 %*                                                                      *
561 %************************************************************************
562
563 \begin{code}
564 type TypeEnv = NameEnv TyThing
565
566 emptyTypeEnv   :: TypeEnv
567 typeEnvElts    :: TypeEnv -> [TyThing]
568 typeEnvClasses :: TypeEnv -> [Class]
569 typeEnvTyCons  :: TypeEnv -> [TyCon]
570 typeEnvIds     :: TypeEnv -> [Id]
571 lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
572
573 emptyTypeEnv       = emptyNameEnv
574 typeEnvElts    env = nameEnvElts env
575 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
576 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
577 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
578
579 mkTypeEnv :: [TyThing] -> TypeEnv
580 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
581                 
582 lookupTypeEnv = lookupNameEnv
583
584 -- Extend the type environment
585 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
586 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
587
588 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
589 extendTypeEnvList env things = foldl extendTypeEnv env things
590 \end{code}
591
592 \begin{code}
593 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
594 lookupType hpt pte name
595   = case lookupModuleEnv hpt (nameModule name) of
596         Just details -> lookupNameEnv (md_types (hm_details details)) name
597         Nothing      -> lookupNameEnv pte name
598 \end{code}
599
600
601 \begin{code}
602 tyThingTyCon (ATyCon tc) = tc
603 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
604
605 tyThingClass (AClass cls) = cls
606 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
607
608 tyThingDataCon (ADataCon dc) = dc
609 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
610
611 tyThingId (AnId id) = id
612 tyThingId other     = pprPanic "tyThingId" (ppr other)
613 \end{code}
614
615 %************************************************************************
616 %*                                                                      *
617 \subsection{Auxiliary types}
618 %*                                                                      *
619 %************************************************************************
620
621 These types are defined here because they are mentioned in ModDetails,
622 but they are mostly elaborated elsewhere
623
624 \begin{code}
625 mkIfaceVerCache :: [(Version,IfaceDecl)] -> OccName -> Maybe Version
626 mkIfaceVerCache pairs 
627   = \occ -> lookupOccEnv env occ
628   where
629     env = foldl add emptyOccEnv pairs
630     add env (v,d) = extendOccEnv env (ifName d) v
631
632 emptyIfaceVerCache :: OccName -> Maybe Version
633 emptyIfaceVerCache occ = Nothing
634
635 ------------------ Deprecations -------------------------
636 data Deprecs a
637   = NoDeprecs
638   | DeprecAll DeprecTxt -- Whole module deprecated
639   | DeprecSome a        -- Some specific things deprecated
640   deriving( Eq )
641
642 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
643 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
644
645 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
646 mkIfaceDepCache NoDeprecs         = \n -> Nothing
647 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
648 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
649
650 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
651 emptyIfaceDepCache n = Nothing
652
653 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
654 lookupDeprec NoDeprecs        name = Nothing
655 lookupDeprec (DeprecAll  txt) name = Just txt
656 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
657                                             Just (_, txt) -> Just txt
658                                             Nothing       -> Nothing
659
660 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
661 plusDeprecs d NoDeprecs = d
662 plusDeprecs NoDeprecs d = d
663 plusDeprecs d (DeprecAll t) = DeprecAll t
664 plusDeprecs (DeprecAll t) d = DeprecAll t
665 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
666 \end{code}
667
668
669 \begin{code}
670 type Avails       = [AvailInfo]
671 type AvailInfo    = GenAvailInfo Name
672 type RdrAvailInfo = GenAvailInfo OccName
673
674 data GenAvailInfo name  = Avail name     -- An ordinary identifier
675                         | AvailTC name   -- The name of the type or class
676                                   [name] -- The available pieces of type/class.
677                                          -- NB: If the type or class is itself
678                                          -- to be in scope, it must be in this list.
679                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
680                         deriving( Eq )
681                         -- Equality used when deciding if the interface has changed
682
683 type IfaceExport = (Module, [GenAvailInfo OccName])
684
685 availsToNameSet :: [AvailInfo] -> NameSet
686 availsToNameSet avails = foldl add emptyNameSet avails
687                        where
688                          add set avail = addListToNameSet set (availNames avail)
689
690 availName :: GenAvailInfo name -> name
691 availName (Avail n)     = n
692 availName (AvailTC n _) = n
693
694 availNames :: GenAvailInfo name -> [name]
695 availNames (Avail n)      = [n]
696 availNames (AvailTC n ns) = ns
697
698 instance Outputable n => Outputable (GenAvailInfo n) where
699    ppr = pprAvail
700
701 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
702 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
703                                         []  -> empty
704                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
705
706 pprAvail (Avail n) = ppr n
707 \end{code}
708
709 \begin{code}
710 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
711 mkIfaceFixCache pairs 
712   = \n -> lookupOccEnv env n `orElse` defaultFixity
713   where
714    env = mkOccEnv pairs
715
716 emptyIfaceFixCache :: OccName -> Fixity
717 emptyIfaceFixCache n = defaultFixity
718
719 -- This fixity environment is for source code only
720 type FixityEnv = NameEnv FixItem
721
722 -- We keep the OccName in the range so that we can generate an interface from it
723 data FixItem = FixItem OccName Fixity SrcSpan
724
725 instance Outputable FixItem where
726   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
727
728 emptyFixityEnv :: FixityEnv
729 emptyFixityEnv = emptyNameEnv
730
731 lookupFixity :: FixityEnv -> Name -> Fixity
732 lookupFixity env n = case lookupNameEnv env n of
733                         Just (FixItem _ fix _) -> fix
734                         Nothing                -> defaultFixity
735 \end{code}
736
737
738 %************************************************************************
739 %*                                                                      *
740 \subsection{WhatsImported}
741 %*                                                                      *
742 %************************************************************************
743
744 \begin{code}
745 type WhetherHasOrphans   = Bool
746         -- An "orphan" is 
747         --      * an instance decl in a module other than the defn module for 
748         --              one of the tycons or classes in the instance head
749         --      * a transformation rule in a module other than the one defining
750         --              the function in the head of the rule.
751
752 type IsBootInterface = Bool
753
754 -- Dependency info about modules and packages below this one
755 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
756 --
757 -- Invariant: the dependencies of a module M never includes M
758 -- Invariant: the lists are unordered, with no duplicates
759 data Dependencies
760   = Deps { dep_mods  :: [(Module,IsBootInterface)],     -- Home-package module dependencies
761            dep_pkgs  :: [PackageId],                    -- External package dependencies
762            dep_orphs :: [Module] }                      -- Orphan modules (whether home or external pkg)
763   deriving( Eq )
764         -- Equality used only for old/new comparison in MkIface.addVersionInfo
765
766 noDependencies :: Dependencies
767 noDependencies = Deps [] [] []
768           
769 data Usage
770   = Usage { usg_name     :: Module,                     -- Name of the module
771             usg_mod      :: Version,                    -- Module version
772             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
773             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
774             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
775                                                         -- modules this will always be initialVersion)
776     }       deriving( Eq )
777         -- This type doesn't let you say "I imported f but none of the rules in
778         -- the module". If you use anything in the module you get its rule version
779         -- So if the rules change, you'll recompile, even if you don't use them.
780         -- This is easy to implement, and it's safer: you might not have used the rules last
781         -- time round, but if someone has added a new rule you might need it this time
782
783         -- The export list field is (Just v) if we depend on the export list:
784         --      i.e. we imported the module without saying exactly what we imported
785         -- We need to recompile if the module exports changes, because we might
786         -- now have a name clash in the importing module.
787 \end{code}
788
789
790 %************************************************************************
791 %*                                                                      *
792                 The External Package State
793 %*                                                                      *
794 %************************************************************************
795
796 \begin{code}
797 type PackageTypeEnv  = TypeEnv
798 type PackageRuleBase = RuleBase
799 type PackageInstEnv  = InstEnv
800
801 data ExternalPackageState
802   = EPS {
803         eps_is_boot :: !(ModuleEnv (Module, IsBootInterface)),
804                 -- In OneShot mode (only), home-package modules accumulate in the
805                 -- external package state, and are sucked in lazily.
806                 -- For these home-pkg modules (only) we need to record which are
807                 -- boot modules.  We set this field after loading all the 
808                 -- explicitly-imported interfaces, but before doing anything else
809                 --
810                 -- The Module part is not necessary, but it's useful for
811                 -- debug prints, and it's convenient because this field comes
812                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
813
814         eps_PIT :: !PackageIfaceTable,
815                 -- The ModuleIFaces for modules in external packages
816                 -- whose interfaces we have opened
817                 -- The declarations in these interface files are held in
818                 -- eps_decls, eps_insts, eps_rules (below), not in the 
819                 -- mi_decls fields of the iPIT.  
820                 -- What _is_ in the iPIT is:
821                 --      * The Module 
822                 --      * Version info
823                 --      * Its exports
824                 --      * Fixities
825                 --      * Deprecations
826
827         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
828
829         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
830                                                 --   all the external-package modules
831         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
832
833
834         -- Holding pens for stuff that has been read in from file,
835         -- but not yet slurped into the renamer
836         eps_insts :: !InstPool,
837                 -- The as-yet un-slurped instance decls
838                 -- Decls move from here to eps_inst_env
839                 -- Each instance is 'gated' by the names that must be 
840                 -- available before this instance decl is needed.
841
842         eps_rules :: !RulePool,
843                 -- The as-yet un-slurped rules
844
845         eps_stats :: !EpsStats
846   }
847
848 -- "In" means read from iface files
849 -- "Out" means actually sucked in and type-checked
850 data EpsStats = EpsStats { n_ifaces_in
851                          , n_decls_in, n_decls_out 
852                          , n_rules_in, n_rules_out
853                          , n_insts_in, n_insts_out :: !Int }
854 \end{code}
855
856 The NameCache makes sure that there is just one Unique assigned for
857 each original name; i.e. (module-name, occ-name) pair.  The Name is
858 always stored as a Global, and has the SrcLoc of its binding location.
859 Actually that's not quite right.  When we first encounter the original
860 name, we might not be at its binding site (e.g. we are reading an
861 interface file); so we give it 'noSrcLoc' then.  Later, when we find
862 its binding site, we fix it up.
863
864 Exactly the same is true of the Module stored in the Name.  When we first
865 encounter the occurrence, we may not know the details of the module, so
866 we just store junk.  Then when we find the binding site, we fix it up.
867
868 \begin{code}
869 data NameCache
870  = NameCache {  nsUniqs :: UniqSupply,
871                 -- Supply of uniques
872                 nsNames :: OrigNameCache,
873                 -- Ensures that one original name gets one unique
874                 nsIPs   :: OrigIParamCache
875                 -- Ensures that one implicit parameter name gets one unique
876    }
877
878 type OrigNameCache   = ModuleEnv (OccEnv Name)
879 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
880 \end{code}
881
882 \begin{code}
883 type Gated d = ([Name], (Module, SDoc, d))
884         -- The [Name] 'gate' the declaration; always non-empty
885         -- Module records which module this decl belongs to
886         -- SDoc records the pathname of the file, or similar err-ctxt info
887
888 type RulePool = [Gated IfaceRule]
889
890 addRulesToPool :: RulePool
891               -> [Gated IfaceRule]
892               -> RulePool
893 addRulesToPool rules new_rules = new_rules ++ rules
894
895 -------------------------
896 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
897 -- Add stats for one newly-read interface
898 addEpsInStats stats n_decls n_insts n_rules
899   = stats { n_ifaces_in = n_ifaces_in stats + 1
900           , n_decls_in  = n_decls_in stats + n_decls
901           , n_insts_in  = n_insts_in stats + n_insts
902           , n_rules_in  = n_rules_in stats + n_rules }
903
904 -------------------------
905 type InstPool = NameEnv [Gated IfaceInst]
906         -- The key of the Pool is the Class
907         -- The Names are the TyCons in the instance head
908         -- For example, suppose this is in an interface file
909         --      instance C T where ...
910         -- We want to slurp this decl if both C and T are "visible" in 
911         -- the importing module.  See "The gating story" in RnIfaces for details.
912
913
914 addInstsToPool :: InstPool -> [(Name, Gated IfaceInst)] -> InstPool
915 addInstsToPool insts new_insts
916   = foldr add insts new_insts
917   where
918     add :: (Name, Gated IfaceInst) -> NameEnv [Gated IfaceInst] -> NameEnv [Gated IfaceInst]
919     add (cls,new_inst) insts = extendNameEnv_C combine insts cls [new_inst]
920         where
921           combine old_insts _ = new_inst : old_insts
922 \end{code}
923
924
925 %************************************************************************
926 %*                                                                      *
927                 The module graph and ModSummary type
928         A ModSummary is a node in the compilation manager's
929         dependency graph, and it's also passed to hscMain
930 %*                                                                      *
931 %************************************************************************
932
933 A ModuleGraph contains all the nodes from the home package (only).  
934 There will be a node for each source module, plus a node for each hi-boot
935 module.
936
937 \begin{code}
938 type ModuleGraph = [ModSummary]  -- The module graph, 
939                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
940
941 emptyMG :: ModuleGraph
942 emptyMG = []
943
944 -- The nodes of the module graph are
945 --      EITHER a regular Haskell source module
946 --      OR     a hi-boot source module
947
948 data ModSummary
949    = ModSummary {
950         ms_mod       :: Module,                 -- Name of the module
951         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
952         ms_location  :: ModLocation,            -- Location
953         ms_hs_date   :: ClockTime,              -- Timestamp of source file
954         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
955         ms_srcimps   :: [Module],               -- Source imports
956         ms_imps      :: [Module],               -- Non-source imports
957         ms_hspp_file :: Maybe FilePath,         -- Filename of preprocessed source,
958                                                 -- once we have preprocessed it.
959         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
960      }
961
962 -- The ModLocation contains both the original source filename and the
963 -- filename of the cleaned-up source file after all preprocessing has been
964 -- done.  The point is that the summariser will have to cpp/unlit/whatever
965 -- all files anyway, and there's no point in doing this twice -- just 
966 -- park the result in a temp file, put the name of it in the location,
967 -- and let @compile@ read from that file on the way back up.
968
969 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
970 -- the ms_hs_date and imports can, of course, change
971
972 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
973 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
974 msHiFilePath  ms = ml_hi_file  (ms_location ms)
975 msObjFilePath ms = ml_obj_file (ms_location ms)
976
977 isBootSummary :: ModSummary -> Bool
978 isBootSummary ms = isHsBoot (ms_hsc_src ms)
979
980 instance Outputable ModSummary where
981    ppr ms
982       = sep [text "ModSummary {",
983              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
984                           text "ms_mod =" <+> ppr (ms_mod ms) 
985                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
986                           text "ms_imps =" <+> ppr (ms_imps ms),
987                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
988              char '}'
989             ]
990
991 showModMsg :: Bool -> ModSummary -> String
992 showModMsg use_object mod_summary
993   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
994                     char '(', text (msHsFilePath mod_summary) <> comma,
995                     if use_object then text (msObjFilePath mod_summary)
996                               else text "interpreted",
997                     char ')'])
998  where 
999     mod     = ms_mod mod_summary 
1000     mod_str = moduleUserString mod ++ hscSourceString (ms_hsc_src mod_summary)
1001 \end{code}
1002
1003
1004 %************************************************************************
1005 %*                                                                      *
1006 \subsection{Linkable stuff}
1007 %*                                                                      *
1008 %************************************************************************
1009
1010 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1011 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1012
1013 \begin{code}
1014 data Linkable = LM {
1015   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1016                                         -- (i.e. when the bytecodes were produced,
1017                                         --       or the mod date on the files)
1018   linkableModule   :: Module,           -- Should be Module, but see below
1019   linkableUnlinked :: [Unlinked]
1020  }
1021
1022 isObjectLinkable :: Linkable -> Bool
1023 isObjectLinkable l = all isObject (linkableUnlinked l)
1024
1025 instance Outputable Linkable where
1026    ppr (LM when_made mod unlinkeds)
1027       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1028         $$ nest 3 (ppr unlinkeds)
1029
1030 -------------------------------------------
1031 data Unlinked
1032    = DotO FilePath
1033    | DotA FilePath
1034    | DotDLL FilePath
1035    | BCOs CompiledByteCode
1036
1037 #ifndef GHCI
1038 data CompiledByteCode = NoByteCode
1039 #endif
1040
1041 instance Outputable Unlinked where
1042    ppr (DotO path)   = text "DotO" <+> text path
1043    ppr (DotA path)   = text "DotA" <+> text path
1044    ppr (DotDLL path) = text "DotDLL" <+> text path
1045 #ifdef GHCI
1046    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1047 #else
1048    ppr (BCOs bcos)   = text "No byte code"
1049 #endif
1050
1051 isObject (DotO _)   = True
1052 isObject (DotA _)   = True
1053 isObject (DotDLL _) = True
1054 isObject _          = False
1055
1056 isInterpretable = not . isObject
1057
1058 nameOfObject (DotO fn)   = fn
1059 nameOfObject (DotA fn)   = fn
1060 nameOfObject (DotDLL fn) = fn
1061
1062 byteCodeOfObject (BCOs bc) = bc
1063 \end{code}
1064
1065
1066