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