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