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