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