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