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