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