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