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