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