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