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