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