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