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