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