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