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