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