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