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