GHC API: add checkAndLoadModule
[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(..), withSession, modifySession, 
10         HscEnv(..), hscEPS,
11         FinderCache, FindResult(..), ModLocationCache,
12         Target(..), TargetId(..), pprTarget, pprTargetId,
13         ModuleGraph, emptyMG,
14
15         ModDetails(..), emptyModDetails,
16         ModGuts(..), CoreModule(..), CgGuts(..), ModImports(..), ForeignStubs(..),
17         ImportedMods,
18
19         ModSummary(..), ms_mod_name, showModMsg, isBootSummary,
20         msHsFilePath, msHiFilePath, msObjFilePath, 
21
22         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
23         
24         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
25         hptInstances, hptRules, hptVectInfo,
26
27         ExternalPackageState(..), EpsStats(..), addEpsInStats,
28         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
29         lookupIfaceByModule, emptyModIface,
30
31         InteractiveContext(..), emptyInteractiveContext, 
32         icPrintUnqual, mkPrintUnqualified, extendInteractiveContext,
33         substInteractiveContext,
34
35         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
36         emptyIfaceDepCache,
37
38         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
39
40         implicitTyThings, isImplicitTyThing,
41
42         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
43         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
44         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
45         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
46         typeEnvDataCons,
47
48         WhetherHasOrphans, IsBootInterface, Usage(..), 
49         Dependencies(..), noDependencies,
50         NameCache(..), OrigNameCache, OrigIParamCache,
51         Avails, availsToNameSet, availsToNameEnv, availName, availNames,
52         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
53         IfaceExport,
54
55         Deprecations(..), DeprecTxt, plusDeprecs,
56
57         PackageInstEnv, PackageRuleBase,
58
59         -- Linker stuff
60         Linkable(..), isObjectLinkable,
61         Unlinked(..), CompiledByteCode,
62         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
63         HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
64
65         -- Breakpoints
66         ModBreaks (..), BreakIndex, emptyModBreaks,
67
68         -- Vectorisation information
69         VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo, 
70         noIfaceVectInfo
71     ) where
72
73 #include "HsVersions.h"
74
75 #ifdef GHCI
76 import ByteCodeAsm      ( CompiledByteCode )
77 import {-# SOURCE #-}  InteractiveEval ( Resume )
78 #endif
79
80 import RdrName
81 import Name             ( Name, NamedThing, getName, nameOccName, nameModule )
82 import NameEnv
83 import NameSet  
84 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
85                           extendOccEnv )
86 import Module
87 import InstEnv          ( InstEnv, Instance )
88 import FamInstEnv       ( FamInstEnv, FamInst )
89 import Rules            ( RuleBase )
90 import CoreSyn          ( CoreBind )
91 import VarEnv
92 import VarSet
93 import Var       hiding ( setIdType )
94 import Id
95 import Type             
96
97 import Class            ( Class, classSelIds, classATs, classTyCon )
98 import TyCon
99 import DataCon          ( DataCon, dataConImplicitIds )
100 import PrelNames        ( gHC_PRIM )
101 import Packages hiding ( Version(..) )
102 import DynFlags         ( DynFlags(..), isOneShot, HscTarget (..) )
103 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
104 import BasicTypes       ( Version, initialVersion, IPName, 
105                           Fixity, defaultFixity, DeprecTxt )
106 import IfaceSyn
107 import FiniteMap        ( FiniteMap )
108 import CoreSyn          ( CoreRule )
109 import Maybes           ( orElse, expectJust, catMaybes, seqMaybe )
110 import Outputable
111 import BreakArray
112 import SrcLoc           ( SrcSpan, Located )
113 import UniqFM           ( lookupUFM, eltsUFM, emptyUFM )
114 import UniqSupply       ( UniqSupply )
115 import FastString       ( FastString )
116 import StringBuffer     ( StringBuffer )
117
118 import System.Time      ( ClockTime )
119 import Data.IORef
120 import Data.Array       ( Array, array )
121 import Data.List
122 \end{code}
123
124
125 %************************************************************************
126 %*                                                                      *
127 \subsection{Compilation environment}
128 %*                                                                      *
129 %************************************************************************
130
131
132 \begin{code}
133 -- | The Session is a handle to the complete state of a compilation
134 -- session.  A compilation session consists of a set of modules
135 -- constituting the current program or library, the context for
136 -- interactive evaluation, and various caches.
137 newtype Session = Session (IORef HscEnv)
138
139 withSession :: Session -> (HscEnv -> IO a) -> IO a
140 withSession (Session ref) f = do h <- readIORef ref; f h
141
142 modifySession :: Session -> (HscEnv -> HscEnv) -> IO ()
143 modifySession (Session ref) f = do h <- readIORef ref; writeIORef ref $! f h
144 \end{code}
145
146 HscEnv is like Session, except that some of the fields are immutable.
147 An HscEnv is used to compile a single module from plain Haskell source
148 code (after preprocessing) to either C, assembly or C--.  Things like
149 the module graph don't change during a single compilation.
150
151 Historical note: "hsc" used to be the name of the compiler binary,
152 when there was a separate driver and compiler.  To compile a single
153 module, the driver would invoke hsc on the source code... so nowadays
154 we think of hsc as the layer of the compiler that deals with compiling
155 a single module.
156
157 \begin{code}
158 data HscEnv 
159   = HscEnv { 
160         hsc_dflags :: DynFlags,
161                 -- The dynamic flag settings
162
163         hsc_targets :: [Target],
164                 -- The targets (or roots) of the current session
165
166         hsc_mod_graph :: ModuleGraph,
167                 -- The module graph of the current session
168
169         hsc_IC :: InteractiveContext,
170                 -- The context for evaluating interactive statements
171
172         hsc_HPT    :: HomePackageTable,
173                 -- The home package table describes already-compiled
174                 -- home-packge modules, *excluding* the module we 
175                 -- are compiling right now.
176                 -- (In one-shot mode the current module is the only
177                 --  home-package module, so hsc_HPT is empty.  All other
178                 --  modules count as "external-package" modules.
179                 --  However, even in GHCi mode, hi-boot interfaces are
180                 --  demand-loadeded into the external-package table.)
181                 --
182                 -- hsc_HPT is not mutable because we only demand-load 
183                 -- external packages; the home package is eagerly 
184                 -- loaded, module by module, by the compilation manager.
185                 --      
186                 -- The HPT may contain modules compiled earlier by --make
187                 -- but not actually below the current module in the dependency
188                 -- graph.  (This changes a previous invariant: changed Jan 05.)
189         
190         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
191         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
192                 -- These are side-effected by compiling to reflect
193                 -- sucking in interface files.  They cache the state of
194                 -- external interface files, in effect.
195
196         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
197         hsc_MLC  :: {-# UNPACK #-} !(IORef ModLocationCache),
198                 -- The finder's cache.  This caches the location of modules,
199                 -- so we don't have to search the filesystem multiple times.
200
201         hsc_global_rdr_env :: GlobalRdrEnv,
202         hsc_global_type_env :: TypeEnv
203  }
204
205 hscEPS :: HscEnv -> IO ExternalPackageState
206 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
207
208 -- | A compilation target.
209 --
210 -- A target may be supplied with the actual text of the
211 -- module.  If so, use this instead of the file contents (this
212 -- is for use in an IDE where the file hasn't been saved by
213 -- the user yet).
214 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
215
216 data TargetId
217   = TargetModule ModuleName
218         -- ^ A module name: search for the file
219   | TargetFile FilePath (Maybe Phase)
220         -- ^ A filename: preprocess & parse it to find the module name.
221         -- If specified, the Phase indicates how to compile this file
222         -- (which phase to start from).  Nothing indicates the starting phase
223         -- should be determined from the suffix of the filename.
224   deriving Eq
225
226 pprTarget :: Target -> SDoc
227 pprTarget (Target id _) = pprTargetId id
228
229 instance Outputable Target where
230     ppr = pprTarget
231
232 pprTargetId :: TargetId -> SDoc
233 pprTargetId (TargetModule m) = ppr m
234 pprTargetId (TargetFile f _) = text f
235
236 instance Outputable TargetId where
237     ppr = pprTargetId
238
239 type HomePackageTable  = ModuleNameEnv HomeModInfo
240         -- Domain = modules in the home package
241         -- "home" package name cached here for convenience
242 type PackageIfaceTable = ModuleEnv ModIface
243         -- Domain = modules in the imported packages
244
245 emptyHomePackageTable :: HomePackageTable
246 emptyHomePackageTable  = emptyUFM
247
248 emptyPackageIfaceTable :: PackageIfaceTable
249 emptyPackageIfaceTable = emptyModuleEnv
250
251 data HomeModInfo 
252   = HomeModInfo { hm_iface    :: !ModIface,
253                   hm_details  :: !ModDetails,
254                   hm_linkable :: !(Maybe Linkable) }
255                 -- hm_linkable might be Nothing if:
256                 --   a) this is an .hs-boot module
257                 --   b) temporarily during compilation if we pruned away
258                 --      the old linkable because it was out of date.
259                 -- after a complete compilation (GHC.load), all hm_linkable
260                 -- fields in the HPT will be Just.
261                 --
262                 -- When re-linking a module (hscNoRecomp), we construct
263                 -- the HomModInfo by building a new ModDetails from the
264                 -- old ModIface (only).
265
266 -- | Find the 'ModIface' for a 'Module'
267 lookupIfaceByModule
268         :: DynFlags
269         -> HomePackageTable
270         -> PackageIfaceTable
271         -> Module
272         -> Maybe ModIface
273 lookupIfaceByModule dflags hpt pit mod
274   | modulePackageId mod == thisPackage dflags
275   =     -- The module comes from the home package, so look first
276         -- in the HPT.  If it's not from the home package it's wrong to look
277         -- in the HPT, because the HPT is indexed by *ModuleName* not Module
278     fmap hm_iface (lookupUFM hpt (moduleName mod)) 
279     `seqMaybe` lookupModuleEnv pit mod
280
281   | otherwise = lookupModuleEnv pit mod         -- Look in PIT only 
282
283 -- If the module does come from the home package, why do we look in the PIT as well?
284 -- (a) In OneShot mode, even home-package modules accumulate in the PIT
285 -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
286 --     module is in the PIT, namely GHC.Prim when compiling the base package.
287 -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a packake
288 -- of its own, but it doesn't seem worth the bother.
289 \end{code}
290
291
292 \begin{code}
293 hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
294 -- Find all the instance declarations (of classes and families) that are in
295 -- modules imported by this one, directly or indirectly, and are in the Home
296 -- Package Table.  This ensures that we don't see instances from modules --make
297 -- compiled before this one, but which are not below this one.
298 hptInstances hsc_env want_this_module
299   = let (insts, famInsts) = unzip
300           [ (md_insts details, md_fam_insts details)
301           | mod_info <- eltsUFM (hsc_HPT hsc_env)
302           , want_this_module (moduleName (mi_module (hm_iface mod_info)))
303           , let details = hm_details mod_info ]
304     in
305     (concat insts, concat famInsts)
306
307 hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
308 -- Get rules from modules "below" this one (in the dependency sense)
309 -- C.f Inst.hptInstances
310 hptRules hsc_env deps
311   | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
312   | otherwise
313   = let 
314         hpt = hsc_HPT hsc_env
315     in
316     [ rule
317     |   -- Find each non-hi-boot module below me
318       (mod, False) <- deps
319
320         -- unsavoury: when compiling the base package with --make, we
321         -- sometimes try to look up RULES for GHC.Prim.  GHC.Prim won't
322         -- be in the HPT, because we never compile it; it's in the EPT
323         -- instead.  ToDo: clean up, and remove this slightly bogus
324         -- filter:
325     , mod /= moduleName gHC_PRIM
326
327         -- Look it up in the HPT
328     , let rules = case lookupUFM hpt mod of
329                     Just info -> md_rules (hm_details info)
330                     Nothing -> pprTrace "WARNING in hptRules" msg [] 
331           msg = vcat [ptext SLIT("missing module") <+> ppr mod,
332                       ptext SLIT("Probable cause: out-of-date interface files")]
333                         -- This really shouldn't happen, but see Trac #962
334
335         -- And get its dfuns
336     , rule <- rules ]
337
338 hptVectInfo :: HscEnv -> VectInfo
339 -- Get the combined VectInfo of all modules in the home package table.  In
340 -- contrast to instances and rules, we don't care whether the modules are
341 -- "below" or us.  The VectInfo of those modules not "below" us does not
342 -- affect the compilation of the current module.
343 hptVectInfo hsc_env 
344   = foldr plusVectInfo noVectInfo [ md_vect_info (hm_details mod_info)
345                                   | mod_info <- eltsUFM (hsc_HPT hsc_env)]
346 \end{code}
347
348 %************************************************************************
349 %*                                                                      *
350 \subsection{The Finder cache}
351 %*                                                                      *
352 %************************************************************************
353
354 \begin{code}
355 -- | The 'FinderCache' maps home module names to the result of
356 -- searching for that module.  It records the results of searching for
357 -- modules along the search path.  On @:load@, we flush the entire
358 -- contents of this cache.
359 --
360 -- Although the @FinderCache@ range is 'FindResult' for convenience ,
361 -- in fact it will only ever contain 'Found' or 'NotFound' entries.
362 --
363 type FinderCache = ModuleNameEnv FindResult
364
365 -- | The result of searching for an imported module.
366 data FindResult
367   = Found ModLocation Module
368         -- the module was found
369   | NoPackage PackageId
370         -- the requested package was not found
371   | FoundMultiple [PackageId]
372         -- *error*: both in multiple packages
373   | PackageHidden PackageId
374         -- for an explicit source import: the package containing the module is
375         -- not exposed.
376   | ModuleHidden  PackageId
377         -- for an explicit source import: the package containing the module is
378         -- exposed, but the module itself is hidden.
379   | NotFound [FilePath] (Maybe PackageId)
380         -- the module was not found, the specified places were searched
381   | NotFoundInPackage PackageId
382         -- the module was not found in this package
383
384 -- | Cache that remembers where we found a particular module.  Contains both
385 -- home modules and package modules.  On @:load@, only home modules are
386 -- purged from this cache.
387 type ModLocationCache = ModuleEnv ModLocation
388 \end{code}
389
390 %************************************************************************
391 %*                                                                      *
392 \subsection{Symbol tables and Module details}
393 %*                                                                      *
394 %************************************************************************
395
396 A @ModIface@ plus a @ModDetails@ summarises everything we know 
397 about a compiled module.  The @ModIface@ is the stuff *before* linking,
398 and can be written out to an interface file.  (The @ModDetails@ is after 
399 linking; it is the "linked" form of the mi_decls field.)
400
401 When we *read* an interface file, we also construct a @ModIface@ from it,
402 except that the mi_decls part is empty; when reading we consolidate
403 the declarations into a single indexed map in the @PersistentRenamerState@.
404
405 \begin{code}
406 data ModIface 
407    = ModIface {
408         mi_module   :: !Module,
409         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
410
411         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
412         mi_finsts   :: !WhetherHasFamInst,  -- Whether module has family insts
413         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
414
415         mi_deps     :: Dependencies,
416                 -- This is consulted for directly-imported modules,
417                 -- but not for anything else (hence lazy)
418
419                 -- Usages; kept sorted so that it's easy to decide
420                 -- whether to write a new iface file (changing usages
421                 -- doesn't affect the version of this module)
422         mi_usages   :: [Usage],
423                 -- NOT STRICT!  we read this field lazily from the interface file
424                 -- It is *only* consulted by the recompilation checker
425
426                 -- Exports
427                 -- Kept sorted by (mod,occ), to make version comparisons easier
428         mi_exports  :: ![IfaceExport],
429         mi_exp_vers :: !Version,        -- Version number of export list
430
431                 -- Fixities
432         mi_fixities :: [(OccName,Fixity)],
433                 -- NOT STRICT!  we read this field lazily from the interface file
434
435                 -- Deprecations
436         mi_deprecs  :: Deprecations,
437                 -- NOT STRICT!  we read this field lazily from the interface file
438
439                 -- Type, class and variable declarations
440                 -- The version of an Id changes if its fixity or deprecations change
441                 --      (as well as its type of course)
442                 -- Ditto data constructors, class operations, except that 
443                 -- the version of the parent class/tycon changes
444         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
445
446         mi_globals  :: !(Maybe GlobalRdrEnv),
447                 -- Binds all the things defined at the top level in
448                 -- the *original source* code for this module. which
449                 -- is NOT the same as mi_exports, nor mi_decls (which
450                 -- may contains declarations for things not actually
451                 -- defined by the user).  Used for GHCi and for inspecting
452                 -- the contents of modules via the GHC API only.
453                 --
454                 -- (We need the source file to figure out the
455                 -- top-level environment, if we didn't compile this module
456                 -- from source then this field contains Nothing).
457                 --
458                 -- Strictly speaking this field should live in the
459                 -- HomeModInfo, but that leads to more plumbing.
460
461                 -- Instance declarations and rules
462         mi_insts     :: [IfaceInst],                    -- Sorted
463         mi_fam_insts :: [IfaceFamInst],                 -- Sorted
464         mi_rules     :: [IfaceRule],                    -- Sorted
465         mi_rule_vers :: !Version,       -- Version number for rules and 
466                                         -- instances (for classes and families)
467                                         -- combined
468
469                 -- Vectorisation information
470         mi_vect_info :: !IfaceVectInfo,
471
472                 -- Cached environments for easy lookup
473                 -- These are computed (lazily) from other fields
474                 -- and are not put into the interface file
475         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
476         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
477         mi_ver_fn  :: OccName -> Maybe (OccName, Version),
478                         -- Cached lookup for mi_decls
479                         -- The Nothing in mi_ver_fn means that the thing
480                         -- isn't in decls. It's useful to know that when
481                         -- seeing if we are up to date wrt the old interface
482                         -- The 'OccName' is the parent of the name, if it has one.
483         mi_hpc    :: !AnyHpcUsage
484           -- True if this program uses Hpc at any point in the program.
485      }
486
487 -- Should be able to construct ModDetails from mi_decls in ModIface
488 data ModDetails
489    = ModDetails {
490         -- The next two fields are created by the typechecker
491         md_exports   :: [AvailInfo],
492         md_types     :: !TypeEnv,
493         md_insts     :: ![Instance],  -- Dfun-ids for the instances in this module
494         md_fam_insts :: ![FamInst],
495         md_rules     :: ![CoreRule],  -- Domain may include Ids from other modules
496         md_vect_info :: !VectInfo     -- Vectorisation information
497      }
498
499 emptyModDetails :: ModDetails
500 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
501                                md_exports = [],
502                                md_insts     = [],
503                                md_rules     = [],
504                                md_fam_insts = [],
505                                md_vect_info = noVectInfo
506                              } 
507
508 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
509 -- There is only one ModGuts at any time, the one for the module
510 -- being compiled right now.  Once it is compiled, a ModIface and 
511 -- ModDetails are extracted and the ModGuts is dicarded.
512
513 type ImportedMods = ModuleEnv (Module, [(ModuleName, Bool, SrcSpan)])
514
515 data ModGuts
516   = ModGuts {
517         mg_module    :: !Module,
518         mg_boot      :: IsBootInterface, -- Whether it's an hs-boot module
519         mg_exports   :: ![AvailInfo],    -- What it exports
520         mg_deps      :: !Dependencies,   -- What is below it, directly or
521                                          --   otherwise 
522         mg_dir_imps  :: !ImportedMods,   -- Directly-imported modules; used to
523                                          --     generate initialisation code
524         mg_used_names:: !NameSet,        -- What it needed (used in mkIface)
525
526         mg_rdr_env   :: !GlobalRdrEnv,   -- Top-level lexical environment
527
528         -- These fields all describe the things **declared in this module**
529         mg_fix_env   :: !FixityEnv,      -- Fixities
530         mg_types     :: !TypeEnv,
531         mg_insts     :: ![Instance],     -- Instances 
532         mg_fam_insts :: ![FamInst],      -- Instances 
533         mg_rules     :: ![CoreRule],     -- Rules from this module
534         mg_binds     :: ![CoreBind],     -- Bindings for this module
535         mg_foreign   :: !ForeignStubs,
536         mg_deprecs   :: !Deprecations,   -- Deprecations declared in the module
537         mg_hpc_info  :: !HpcInfo,        -- info about coverage tick boxes
538         mg_modBreaks :: !ModBreaks,
539         mg_vect_info :: !VectInfo,        -- Pool of vectorised declarations
540
541         -- The next two fields are unusual, because they give instance
542         -- environments for *all* modules in the home package, including
543         -- this module, rather than for *just* this module.  
544         -- Reason: when looking up an instance we don't want to have to
545         --        look at each module in the home package in turn
546         mg_inst_env     :: InstEnv,      -- Class instance enviroment fro
547                                          -- *home-package* modules (including
548                                          -- this one); c.f. tcg_inst_env
549         mg_fam_inst_env :: FamInstEnv    -- Type-family instance enviroment
550                                          -- for *home-package* modules (including
551                                          -- this one); c.f. tcg_fam_inst_env
552     }
553
554 -- A CoreModule consists of just the fields of a ModGuts that are needed for
555 -- the compileToCoreModule interface.
556 data CoreModule
557   = CoreModule {
558       -- Module name
559       cm_module   :: !Module,
560       -- Type environment for types declared in this module
561       cm_types    :: !TypeEnv,
562       -- Declarations
563       cm_binds    :: [CoreBind]
564     }
565
566 instance Outputable CoreModule where
567    ppr (CoreModule {cm_module = mn, cm_types = te, cm_binds = cb}) =
568       text "%module" <+> ppr mn <+> ppr te $$ vcat (map ppr cb)
569
570 -- The ModGuts takes on several slightly different forms:
571 --
572 -- After simplification, the following fields change slightly:
573 --      mg_rules        Orphan rules only (local ones now attached to binds)
574 --      mg_binds        With rules attached
575
576
577 ---------------------------------------------------------
578 -- The Tidy pass forks the information about this module: 
579 --      * one lot goes to interface file generation (ModIface)
580 --        and later compilations (ModDetails)
581 --      * the other lot goes to code generation (CgGuts)
582 data CgGuts 
583   = CgGuts {
584         cg_module   :: !Module,
585
586         cg_tycons   :: [TyCon],
587                 -- Algebraic data types (including ones that started
588                 -- life as classes); generate constructors and info
589                 -- tables Includes newtypes, just for the benefit of
590                 -- External Core
591
592         cg_binds    :: [CoreBind],
593                 -- The tidied main bindings, including
594                 -- previously-implicit bindings for record and class
595                 -- selectors, and data construtor wrappers.  But *not*
596                 -- data constructor workers; reason: we we regard them
597                 -- as part of the code-gen of tycons
598
599         cg_dir_imps :: ![Module],
600                 -- Directly-imported modules; used to generate
601                 -- initialisation code
602
603         cg_foreign  :: !ForeignStubs,   
604         cg_dep_pkgs :: ![PackageId],    -- Used to generate #includes for C code gen
605         cg_hpc_info :: !HpcInfo,         -- info about coverage tick boxes
606         cg_modBreaks :: !ModBreaks
607     }
608
609 -----------------------------------
610 data ModImports
611   = ModImports {
612         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
613                                                 -- Boolean is true if we imported the whole
614                                                 --      module (apart, perhaps, from hiding some)
615         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
616                                                 --      directly or indirectly
617         imp_home_names :: !NameSet              -- Home package things on which we depend,
618                                                 --      directly or indirectly
619     }
620
621 -----------------------------------
622 data ForeignStubs = NoStubs
623                   | ForeignStubs
624                         SDoc            -- Header file prototypes for
625                                         --      "foreign exported" functions
626                         SDoc            -- C stubs to use when calling
627                                         --      "foreign exported" functions
628                         [FastString]    -- Headers that need to be included
629                                         --      into C code generated for this module
630
631 \end{code}
632
633 \begin{code}
634 emptyModIface :: Module -> ModIface
635 emptyModIface mod
636   = ModIface { mi_module   = mod,
637                mi_mod_vers = initialVersion,
638                mi_orphan   = False,
639                mi_finsts   = False,
640                mi_boot     = False,
641                mi_deps     = noDependencies,
642                mi_usages   = [],
643                mi_exports  = [],
644                mi_exp_vers = initialVersion,
645                mi_fixities = [],
646                mi_deprecs  = NoDeprecs,
647                mi_insts     = [],
648                mi_fam_insts = [],
649                mi_rules     = [],
650                mi_decls     = [],
651                mi_globals   = Nothing,
652                mi_rule_vers = initialVersion,
653                mi_vect_info = noIfaceVectInfo,
654                mi_dep_fn = emptyIfaceDepCache,
655                mi_fix_fn = emptyIfaceFixCache,
656                mi_ver_fn = emptyIfaceVerCache,
657                mi_hpc    = False
658     }           
659 \end{code}
660
661
662 %************************************************************************
663 %*                                                                      *
664 \subsection{The interactive context}
665 %*                                                                      *
666 %************************************************************************
667
668 \begin{code}
669 data InteractiveContext 
670   = InteractiveContext { 
671         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
672                                         -- these modules
673
674         ic_exports :: [Module],         -- Include just the exports of these
675                                         -- modules
676
677         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
678                                         -- ic_toplev_scope and ic_exports
679
680         ic_tmp_ids :: [Id],             -- Names bound during interaction.
681                                         -- Later Ids shadow
682                                         -- earlier ones with the same OccName.
683
684         ic_tyvars :: TyVarSet           -- skolem type variables free in
685                                         -- ic_tmp_ids.  These arise at
686                                         -- breakpoints in a polymorphic 
687                                         -- context, where we have only partial
688                                         -- type information.
689
690 #ifdef GHCI
691         , ic_resume :: [Resume]         -- the stack of breakpoint contexts
692 #endif
693     }
694
695
696 emptyInteractiveContext :: InteractiveContext
697 emptyInteractiveContext
698   = InteractiveContext { ic_toplev_scope = [],
699                          ic_exports = [],
700                          ic_rn_gbl_env = emptyGlobalRdrEnv,
701                          ic_tmp_ids = [],
702                          ic_tyvars = emptyVarSet
703 #ifdef GHCI
704                          , ic_resume = []
705 #endif
706                        }
707
708 icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
709 icPrintUnqual dflags ictxt = mkPrintUnqualified dflags (ic_rn_gbl_env ictxt)
710
711
712 extendInteractiveContext
713         :: InteractiveContext
714         -> [Id]
715         -> TyVarSet
716         -> InteractiveContext
717 extendInteractiveContext ictxt ids tyvars
718   = ictxt { ic_tmp_ids =  ic_tmp_ids ictxt ++ ids,
719                           -- NB. must be this way around, because we want
720                           -- new ids to shadow existing bindings.
721             ic_tyvars   = ic_tyvars ictxt `unionVarSet` tyvars }
722
723
724 substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
725 substInteractiveContext ictxt subst | isEmptyTvSubst subst = ictxt
726 substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst =
727    let ids'     = map (\id -> id `setIdType` substTy subst (idType id)) ids
728        subst_dom= varEnvKeys$ getTvSubstEnv subst
729        subst_ran= varEnvElts$ getTvSubstEnv subst
730        new_tvs  = [ tv | Just tv <- map getTyVar_maybe subst_ran]  
731        ic_tyvars'= (`delVarSetListByKey` subst_dom) 
732                  . (`extendVarSetList`   new_tvs)
733                    $ ic_tyvars ictxt
734     in ictxt { ic_tmp_ids = ids'
735              , ic_tyvars   = ic_tyvars' }
736
737           where delVarSetListByKey = foldl' delVarSetByKey
738 \end{code}
739
740 %************************************************************************
741 %*                                                                      *
742         Building a PrintUnqualified             
743 %*                                                                      *
744 %************************************************************************
745
746 Deciding how to print names is pretty tricky.  We are given a name
747 P:M.T, where P is the package name, M is the defining module, and T is
748 the occurrence name, and we have to decide in which form to display
749 the name given a GlobalRdrEnv describing the current scope.
750
751 Ideally we want to display the name in the form in which it is in
752 scope.  However, the name might not be in scope at all, and that's
753 where it gets tricky.  Here are the cases:
754
755  1. T   uniquely maps to  P:M.T                         --->  "T"
756  2. there is an X for which X.T uniquely maps to  P:M.T --->  "X.T"
757  3. there is no binding for "M.T"                       --->  "M.T"
758  4. otherwise                                           --->  "P:M.T"
759
760 3 and 4 apply when P:M.T is not in scope.  In these cases we want to
761 refer to the name as "M.T", but "M.T" might mean something else in the
762 current scope (e.g. if there's an "import X as M"), so to avoid
763 confusion we avoid using "M.T" if there's already a binding for it.
764
765 There's one further subtlety: if the module M cannot be imported
766 because it is not exposed by any package, then we must refer to it as
767 "P:M".  This is handled by the qual_mod component of PrintUnqualified.
768
769 \begin{code}
770 mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
771 mkPrintUnqualified dflags env = (qual_name, qual_mod)
772   where
773   qual_name mod occ     -- The (mod,occ) pair is the original name of the thing
774         | [gre] <- unqual_gres, right_name gre = NameUnqual
775                 -- If there's a unique entity that's in scope unqualified with 'occ'
776                 -- AND that entity is the right one, then we can use the unqualified name
777
778         | [gre] <- qual_gres = NameQual (get_qual_mod (gre_prov gre))
779
780         | null qual_gres = 
781               if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
782                    then NameNotInScope1
783                    else NameNotInScope2
784
785         | otherwise = panic "mkPrintUnqualified"
786       where
787         right_name gre = nameModule (gre_name gre) == mod
788
789         unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
790         qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
791
792         get_qual_mod LocalDef      = moduleName mod
793         get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
794
795     -- we can mention a module P:M without the P: qualifier iff
796     -- "import M" would resolve unambiguously to P:M.  (if P is the
797     -- current package we can just assume it is unqualified).
798
799   qual_mod mod
800      | modulePackageId mod == thisPackage dflags = False
801
802      | [pkgconfig] <- [pkg | (pkg,exposed_module) <- lookup, 
803                              exposed pkg && exposed_module],
804        packageConfigId pkgconfig == modulePackageId mod
805         -- this says: we are given a module P:M, is there just one exposed package
806         -- that exposes a module M, and is it package P?
807      = False
808
809      | otherwise = True
810      where lookup = lookupModuleInAllPackages dflags (moduleName mod)
811 \end{code}
812
813
814 %************************************************************************
815 %*                                                                      *
816                 TyThing
817 %*                                                                      *
818 %************************************************************************
819
820 \begin{code}
821 -- N.B. the set of TyThings returned here *must* match the set of
822 -- names returned by LoadIface.ifaceDeclSubBndrs, in the sense that
823 -- TyThing.getOccName should define a bijection between the two lists.
824 -- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop])
825 -- The order of the list does not matter.
826 implicitTyThings :: TyThing -> [TyThing]
827
828 -- For data and newtype declarations:
829 implicitTyThings (ATyCon tc) = 
830     -- fields (names of selectors)
831     map AnId (tyConSelIds tc) ++ 
832     -- (possibly) implicit coercion and family coercion
833     --   depending on whether it's a newtype or a family instance or both
834     implicitCoTyCon tc ++
835     -- for each data constructor in order,
836     --   the contructor, worker, and (possibly) wrapper
837     concatMap (extras_plus . ADataCon) (tyConDataCons tc)
838                      
839 implicitTyThings (AClass cl) 
840   = -- dictionary datatype:
841     --    [extras_plus:]
842     --      type constructor 
843     --    [recursive call:]
844     --      (possibly) newtype coercion; definitely no family coercion here
845     --      data constructor
846     --      worker
847     --      (no wrapper by invariant)
848     extras_plus (ATyCon (classTyCon cl)) ++
849     -- associated types 
850     --    No extras_plus (recursive call) for the classATs, because they
851     --    are only the family decls; they have no implicit things
852     map ATyCon (classATs cl) ++
853     -- superclass and operation selectors
854     map AnId (classSelIds cl)
855
856 implicitTyThings (ADataCon dc) = 
857     -- For data cons add the worker and (possibly) wrapper
858     map AnId (dataConImplicitIds dc)
859
860 implicitTyThings (AnId _)   = []
861
862 -- add a thing and recursive call
863 extras_plus :: TyThing -> [TyThing]
864 extras_plus thing = thing : implicitTyThings thing
865
866 -- For newtypes and indexed data types (and both),
867 -- add the implicit coercion tycon
868 implicitCoTyCon :: TyCon -> [TyThing]
869 implicitCoTyCon tc 
870   = map ATyCon . catMaybes $ [-- Just if newtype, Nothing if not
871                               newTyConCo_maybe tc, 
872                               -- Just if family instance, Nothing if not
873                                 tyConFamilyCoercion_maybe tc] 
874
875 -- sortByOcc = sortBy (\ x -> \ y -> getOccName x < getOccName y)
876
877
878 -- | returns 'True' if there should be no interface-file declaration
879 -- for this thing on its own: either it is built-in, or it is part
880 -- of some other declaration, or it is generated implicitly by some
881 -- other declaration.
882 isImplicitTyThing :: TyThing -> Bool
883 isImplicitTyThing (ADataCon _)  = True
884 isImplicitTyThing (AnId     id) = isImplicitId id
885 isImplicitTyThing (AClass   _)  = False
886 isImplicitTyThing (ATyCon   tc) = isImplicitTyCon tc
887
888 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
889 extendTypeEnvWithIds env ids
890   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
891 \end{code}
892
893 %************************************************************************
894 %*                                                                      *
895                 TypeEnv
896 %*                                                                      *
897 %************************************************************************
898
899 \begin{code}
900 type TypeEnv = NameEnv TyThing
901
902 emptyTypeEnv    :: TypeEnv
903 typeEnvElts     :: TypeEnv -> [TyThing]
904 typeEnvClasses  :: TypeEnv -> [Class]
905 typeEnvTyCons   :: TypeEnv -> [TyCon]
906 typeEnvIds      :: TypeEnv -> [Id]
907 typeEnvDataCons :: TypeEnv -> [DataCon]
908 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
909
910 emptyTypeEnv        = emptyNameEnv
911 typeEnvElts     env = nameEnvElts env
912 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
913 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
914 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
915 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
916
917 mkTypeEnv :: [TyThing] -> TypeEnv
918 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
919                 
920 lookupTypeEnv = lookupNameEnv
921
922 -- Extend the type environment
923 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
924 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
925
926 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
927 extendTypeEnvList env things = foldl extendTypeEnv env things
928 \end{code}
929
930 \begin{code}
931 lookupType :: DynFlags
932            -> HomePackageTable
933            -> PackageTypeEnv
934            -> Name
935            -> Maybe TyThing
936
937 lookupType dflags hpt pte name
938   -- in one-shot, we don't use the HPT
939   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
940   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
941        lookupNameEnv (md_types (hm_details hm)) name
942   | otherwise
943   = lookupNameEnv pte name
944   where mod = nameModule name
945         this_pkg = thisPackage dflags
946 \end{code}
947
948 \begin{code}
949 tyThingTyCon :: TyThing -> TyCon
950 tyThingTyCon (ATyCon tc) = tc
951 tyThingTyCon other       = pprPanic "tyThingTyCon" (pprTyThing other)
952
953 tyThingClass :: TyThing -> Class
954 tyThingClass (AClass cls) = cls
955 tyThingClass other        = pprPanic "tyThingClass" (pprTyThing other)
956
957 tyThingDataCon :: TyThing -> DataCon
958 tyThingDataCon (ADataCon dc) = dc
959 tyThingDataCon other         = pprPanic "tyThingDataCon" (pprTyThing other)
960
961 tyThingId :: TyThing -> Id
962 tyThingId (AnId id) = id
963 tyThingId other     = pprPanic "tyThingId" (pprTyThing other)
964 \end{code}
965
966 %************************************************************************
967 %*                                                                      *
968 \subsection{Auxiliary types}
969 %*                                                                      *
970 %************************************************************************
971
972 These types are defined here because they are mentioned in ModDetails,
973 but they are mostly elaborated elsewhere
974
975 \begin{code}
976 mkIfaceVerCache :: [(Version,IfaceDecl)]
977                 -> (OccName -> Maybe (OccName, Version))
978 mkIfaceVerCache pairs 
979   = \occ -> lookupOccEnv env occ
980   where
981     env = foldr add_decl emptyOccEnv pairs
982     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
983       where
984           decl_name = ifName d
985           env1 = extendOccEnv env0 decl_name (decl_name, v)
986           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
987
988 emptyIfaceVerCache :: OccName -> Maybe (OccName, Version)
989 emptyIfaceVerCache _occ = Nothing
990
991 ------------------ Deprecations -------------------------
992 data Deprecations
993   = NoDeprecs
994   | DeprecAll DeprecTxt         -- Whole module deprecated
995   | DeprecSome [(OccName,DeprecTxt)] -- Some specific things deprecated
996      -- Only an OccName is needed because
997      --    (1) a deprecation always applies to a binding
998      --        defined in the module in which the deprecation appears.
999      --    (2) deprecations are only reported outside the defining module.
1000      --        this is important because, otherwise, if we saw something like
1001      --
1002      --        {-# DEPRECATED f "" #-}
1003      --        f = ...
1004      --        h = f
1005      --        g = let f = undefined in f
1006      --
1007      --        we'd need more information than an OccName to know to say something
1008      --        about the use of f in h but not the use of the locally bound f in g
1009      --
1010      --        however, because we only report about deprecations from the outside,
1011      --        and a module can only export one value called f,
1012      --        an OccName suffices.
1013      --
1014      --        this is in contrast with fixity declarations, where we need to map
1015      --        a Name to its fixity declaration.
1016   deriving( Eq )
1017
1018 mkIfaceDepCache :: Deprecations -> Name -> Maybe DeprecTxt
1019 mkIfaceDepCache NoDeprecs         = \_ -> Nothing
1020 mkIfaceDepCache (DeprecAll t)     = \_ -> Just t
1021 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
1022
1023 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
1024 emptyIfaceDepCache _ = Nothing
1025
1026 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
1027 plusDeprecs d NoDeprecs = d
1028 plusDeprecs NoDeprecs d = d
1029 plusDeprecs _ (DeprecAll t) = DeprecAll t
1030 plusDeprecs (DeprecAll t) _ = DeprecAll t
1031 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 ++ v2)
1032 \end{code}
1033
1034
1035 \begin{code}
1036 type Avails       = [AvailInfo]
1037 type AvailInfo    = GenAvailInfo Name
1038 type RdrAvailInfo = GenAvailInfo OccName
1039
1040 data GenAvailInfo name  = Avail name     -- An ordinary identifier
1041                         | AvailTC name   -- The name of the type or class
1042                                   [name] -- The available pieces of type/class.
1043                                          -- NB: If the type or class is itself
1044                                          -- to be in scope, it must be in this list.
1045                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
1046                         deriving( Eq )
1047                         -- Equality used when deciding if the interface has changed
1048
1049 type IfaceExport = (Module, [GenAvailInfo OccName])
1050
1051 availsToNameSet :: [AvailInfo] -> NameSet
1052 availsToNameSet avails = foldr add emptyNameSet avails
1053       where add avail set = addListToNameSet set (availNames avail)
1054
1055 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
1056 availsToNameEnv avails = foldr add emptyNameEnv avails
1057      where add avail env = extendNameEnvList env
1058                                 (zip (availNames avail) (repeat avail))
1059
1060 availName :: GenAvailInfo name -> name
1061 availName (Avail n)     = n
1062 availName (AvailTC n _) = n
1063
1064 availNames :: GenAvailInfo name -> [name]
1065 availNames (Avail n)      = [n]
1066 availNames (AvailTC _ ns) = ns
1067
1068 instance Outputable n => Outputable (GenAvailInfo n) where
1069    ppr = pprAvail
1070
1071 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
1072 pprAvail (Avail n)      = ppr n
1073 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
1074 \end{code}
1075
1076 \begin{code}
1077 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
1078 mkIfaceFixCache pairs 
1079   = \n -> lookupOccEnv env n `orElse` defaultFixity
1080   where
1081    env = mkOccEnv pairs
1082
1083 emptyIfaceFixCache :: OccName -> Fixity
1084 emptyIfaceFixCache _ = defaultFixity
1085
1086 -- This fixity environment is for source code only
1087 type FixityEnv = NameEnv FixItem
1088
1089 -- We keep the OccName in the range so that we can generate an interface from it
1090 data FixItem = FixItem OccName Fixity
1091
1092 instance Outputable FixItem where
1093   ppr (FixItem occ fix) = ppr fix <+> ppr occ
1094
1095 emptyFixityEnv :: FixityEnv
1096 emptyFixityEnv = emptyNameEnv
1097
1098 lookupFixity :: FixityEnv -> Name -> Fixity
1099 lookupFixity env n = case lookupNameEnv env n of
1100                         Just (FixItem _ fix) -> fix
1101                         Nothing         -> defaultFixity
1102 \end{code}
1103
1104
1105 %************************************************************************
1106 %*                                                                      *
1107 \subsection{WhatsImported}
1108 %*                                                                      *
1109 %************************************************************************
1110
1111 \begin{code}
1112 type WhetherHasOrphans   = Bool
1113         -- An "orphan" is 
1114         --      * an instance decl in a module other than the defn module for 
1115         --              one of the tycons or classes in the instance head
1116         --      * a transformation rule in a module other than the one defining
1117         --              the function in the head of the rule.
1118
1119 type WhetherHasFamInst = Bool        -- This module defines family instances?
1120
1121 type IsBootInterface = Bool
1122
1123 -- Dependency info about modules and packages below this one
1124 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
1125 -- The orphan modules in `dep_orphs' do *not* include family instance orphans,
1126 -- as they are anyway included in `dep_finsts'.
1127 --
1128 -- Invariant: the dependencies of a module M never includes M
1129 -- Invariant: the lists are unordered, with no duplicates
1130 data Dependencies
1131   = Deps { dep_mods   :: [(ModuleName,      -- Home-package module dependencies
1132                            IsBootInterface)]
1133          , dep_pkgs   :: [PackageId]        -- External package dependencies
1134          , dep_orphs  :: [Module]           -- Orphan modules (whether home or
1135                                             -- external pkg)
1136          , dep_finsts :: [Module]           -- Modules that contain family
1137                                             -- instances (whether home or
1138                                             -- external pkg)
1139          }
1140   deriving( Eq )
1141         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1142
1143 noDependencies :: Dependencies
1144 noDependencies = Deps [] [] [] []
1145           
1146 data Usage
1147   = Usage { usg_name     :: ModuleName,                 -- Name of the module
1148             usg_mod      :: Version,                    -- Module version
1149             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
1150                 -- NB. usages are for parent names only, eg. tycon but not constructors.
1151             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
1152             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
1153                                                         -- modules this will always be initialVersion)
1154     }       deriving( Eq )
1155         -- This type doesn't let you say "I imported f but none of the rules in
1156         -- the module". If you use anything in the module you get its rule version
1157         -- So if the rules change, you'll recompile, even if you don't use them.
1158         -- This is easy to implement, and it's safer: you might not have used the rules last
1159         -- time round, but if someone has added a new rule you might need it this time
1160
1161         -- The export list field is (Just v) if we depend on the export list:
1162         --      i.e. we imported the module directly, whether or not we
1163         --           enumerated the things we imported, or just imported everything
1164         -- We need to recompile if M's exports change, because 
1165         -- if the import was    import M,       we might now have a name clash in the 
1166         --                                      importing module.
1167         -- if the import was    import M(x)     M might no longer export x
1168         -- The only way we don't depend on the export list is if we have
1169         --                      import M()
1170         -- And of course, for modules that aren't imported directly we don't
1171         -- depend on their export lists
1172 \end{code}
1173
1174
1175 %************************************************************************
1176 %*                                                                      *
1177                 The External Package State
1178 %*                                                                      *
1179 %************************************************************************
1180
1181 \begin{code}
1182 type PackageTypeEnv    = TypeEnv
1183 type PackageRuleBase   = RuleBase
1184 type PackageInstEnv    = InstEnv
1185 type PackageFamInstEnv = FamInstEnv
1186 type PackageVectInfo   = VectInfo
1187
1188 data ExternalPackageState
1189   = EPS {
1190         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1191                 -- In OneShot mode (only), home-package modules
1192                 -- accumulate in the external package state, and are
1193                 -- sucked in lazily.  For these home-pkg modules
1194                 -- (only) we need to record which are boot modules.
1195                 -- We set this field after loading all the
1196                 -- explicitly-imported interfaces, but before doing
1197                 -- anything else
1198                 --
1199                 -- The ModuleName part is not necessary, but it's useful for
1200                 -- debug prints, and it's convenient because this field comes
1201                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
1202
1203         eps_PIT :: !PackageIfaceTable,
1204                 -- The ModuleIFaces for modules in external packages
1205                 -- whose interfaces we have opened
1206                 -- The declarations in these interface files are held in
1207                 -- eps_decls, eps_inst_env, eps_fam_inst_env, eps_rules
1208                 -- (below), not in the mi_decls fields of the iPIT.  
1209                 -- What _is_ in the iPIT is:
1210                 --      * The Module 
1211                 --      * Version info
1212                 --      * Its exports
1213                 --      * Fixities
1214                 --      * Deprecations
1215
1216         eps_PTE :: !PackageTypeEnv,        -- Domain = external-package modules
1217
1218         eps_inst_env     :: !PackageInstEnv,   -- The total InstEnv accumulated
1219                                                -- from all the external-package
1220                                                -- modules 
1221         eps_fam_inst_env :: !PackageFamInstEnv,-- Ditto FamInstEnv
1222         eps_rule_base    :: !PackageRuleBase,  -- Ditto RuleEnv
1223         eps_vect_info    :: !PackageVectInfo,  -- Ditto VectInfo
1224
1225         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- identifies family
1226                                                        -- instances of each mod 
1227         eps_stats :: !EpsStats
1228   }
1229
1230 -- "In" means read from iface files
1231 -- "Out" means actually sucked in and type-checked
1232 data EpsStats = EpsStats { n_ifaces_in
1233                          , n_decls_in, n_decls_out 
1234                          , n_rules_in, n_rules_out
1235                          , n_insts_in, n_insts_out :: !Int }
1236
1237 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1238 -- Add stats for one newly-read interface
1239 addEpsInStats stats n_decls n_insts n_rules
1240   = stats { n_ifaces_in = n_ifaces_in stats + 1
1241           , n_decls_in  = n_decls_in stats + n_decls
1242           , n_insts_in  = n_insts_in stats + n_insts
1243           , n_rules_in  = n_rules_in stats + n_rules }
1244 \end{code}
1245
1246 The NameCache makes sure that there is just one Unique assigned for
1247 each original name; i.e. (module-name, occ-name) pair.  The Name is
1248 always stored as a Global, and has the SrcLoc of its binding location.
1249 Actually that's not quite right.  When we first encounter the original
1250 name, we might not be at its binding site (e.g. we are reading an
1251 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1252 its binding site, we fix it up.
1253
1254 \begin{code}
1255 data NameCache
1256  = NameCache {  nsUniqs :: UniqSupply,
1257                 -- Supply of uniques
1258                 nsNames :: OrigNameCache,
1259                 -- Ensures that one original name gets one unique
1260                 nsIPs   :: OrigIParamCache
1261                 -- Ensures that one implicit parameter name gets one unique
1262    }
1263
1264 type OrigNameCache   = ModuleEnv (OccEnv Name)
1265 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
1266 \end{code}
1267
1268
1269
1270 %************************************************************************
1271 %*                                                                      *
1272                 The module graph and ModSummary type
1273         A ModSummary is a node in the compilation manager's
1274         dependency graph, and it's also passed to hscMain
1275 %*                                                                      *
1276 %************************************************************************
1277
1278 A ModuleGraph contains all the nodes from the home package (only).  
1279 There will be a node for each source module, plus a node for each hi-boot
1280 module.
1281
1282 \begin{code}
1283 type ModuleGraph = [ModSummary]  -- The module graph, 
1284                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
1285
1286 emptyMG :: ModuleGraph
1287 emptyMG = []
1288
1289 -- The nodes of the module graph are
1290 --      EITHER a regular Haskell source module
1291 --      OR     a hi-boot source module
1292
1293 data ModSummary
1294    = ModSummary {
1295         ms_mod       :: Module,                 -- Identity of the module
1296         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
1297         ms_location  :: ModLocation,            -- Location
1298         ms_hs_date   :: ClockTime,              -- Timestamp of source file
1299         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
1300         ms_srcimps   :: [Located ModuleName],   -- Source imports
1301         ms_imps      :: [Located ModuleName],   -- Non-source imports
1302         ms_hspp_file :: FilePath,               -- Filename of preprocessed source.
1303         ms_hspp_opts :: DynFlags,               -- Cached flags from OPTIONS, INCLUDE
1304                                                 -- and LANGUAGE pragmas.
1305         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
1306      }
1307
1308 ms_mod_name :: ModSummary -> ModuleName
1309 ms_mod_name = moduleName . ms_mod
1310
1311 -- The ModLocation contains both the original source filename and the
1312 -- filename of the cleaned-up source file after all preprocessing has been
1313 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1314 -- all files anyway, and there's no point in doing this twice -- just 
1315 -- park the result in a temp file, put the name of it in the location,
1316 -- and let @compile@ read from that file on the way back up.
1317
1318 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1319 -- the ms_hs_date and imports can, of course, change
1320
1321 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1322 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1323 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1324 msObjFilePath ms = ml_obj_file (ms_location ms)
1325
1326 isBootSummary :: ModSummary -> Bool
1327 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1328
1329 instance Outputable ModSummary where
1330    ppr ms
1331       = sep [text "ModSummary {",
1332              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1333                           text "ms_mod =" <+> ppr (ms_mod ms) 
1334                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1335                           text "ms_imps =" <+> ppr (ms_imps ms),
1336                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1337              char '}'
1338             ]
1339
1340 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1341 showModMsg target recomp mod_summary
1342   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1343                     char '(', text (msHsFilePath mod_summary) <> comma,
1344                     case target of
1345                       HscInterpreted | recomp 
1346                                  -> text "interpreted"
1347                       HscNothing -> text "nothing"
1348                       _other     -> text (msObjFilePath mod_summary),
1349                     char ')'])
1350  where 
1351     mod     = moduleName (ms_mod mod_summary)
1352     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1353 \end{code}
1354
1355
1356 %************************************************************************
1357 %*                                                                      *
1358 \subsection{Hpc Support}
1359 %*                                                                      *
1360 %************************************************************************
1361
1362 \begin{code}
1363 data HpcInfo 
1364   = HpcInfo 
1365      { hpcInfoTickCount :: Int 
1366      , hpcInfoHash      :: Int  
1367      }
1368   | NoHpcInfo 
1369      { hpcUsed          :: AnyHpcUsage  -- is hpc used anywhere on the module tree?
1370      }
1371
1372 -- This is used to mean there is no module-local hpc usage,
1373 -- but one of my imports used hpc instrumentation.
1374
1375 type AnyHpcUsage = Bool
1376
1377 emptyHpcInfo :: AnyHpcUsage -> HpcInfo
1378 emptyHpcInfo = NoHpcInfo 
1379
1380 isHpcUsed :: HpcInfo -> AnyHpcUsage
1381 isHpcUsed (HpcInfo {})                   = True
1382 isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
1383 \end{code}
1384
1385 %************************************************************************
1386 %*                                                                      *
1387 \subsection{Vectorisation Support}
1388 %*                                                                      *
1389 %************************************************************************
1390
1391 The following information is generated and consumed by the vectorisation
1392 subsystem.  It communicates the vectorisation status of declarations from one
1393 module to another.
1394
1395 Why do we need both f and f_v in the ModGuts/ModDetails/EPS version VectInfo
1396 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1397 vectorisation, we need to know `f_v', whose `Var' we cannot lookup based
1398 on just the OccName easily in a Core pass.
1399
1400 \begin{code}
1401 -- ModGuts/ModDetails/EPS version
1402 data VectInfo      
1403   = VectInfo {
1404       vectInfoVar     :: VarEnv  (Var    , Var  ),   -- (f, f_v) keyed on f
1405       vectInfoTyCon   :: NameEnv (TyCon  , TyCon),   -- (T, T_v) keyed on T
1406       vectInfoDataCon :: NameEnv (DataCon, DataCon), -- (C, C_v) keyed on C
1407       vectInfoPADFun  :: NameEnv (TyCon  , Var),     -- (T_v, paT) keyed on T_v
1408       vectInfoIso     :: NameEnv (TyCon  , Var)      -- (T, isoT) keyed on T
1409     }
1410     -- all of this is always tidy, even in ModGuts
1411
1412 -- ModIface version
1413 data IfaceVectInfo 
1414   = IfaceVectInfo {
1415       ifaceVectInfoVar        :: [Name],
1416         -- all variables in here have a vectorised variant;
1417         -- the name of the vectorised variant is determined by `mkCloVect'
1418       ifaceVectInfoTyCon      :: [Name],
1419         -- all tycons in here have a vectorised variant;
1420         -- the name of the vectorised variant and those of its
1421         -- data constructors are determined by `mkVectTyConOcc'
1422         -- and `mkVectDataConOcc'; the names of
1423         -- the isomorphisms is determined by `mkVectIsoOcc'
1424       ifaceVectInfoTyConReuse :: [Name]              
1425         -- the vectorised form of all the tycons in here coincids with
1426         -- the unconverted from; the names of the isomorphisms is determined
1427         -- by `mkVectIsoOcc'
1428     }
1429
1430 noVectInfo :: VectInfo
1431 noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyNameEnv
1432
1433 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1434 plusVectInfo vi1 vi2 = 
1435   VectInfo (vectInfoVar     vi1 `plusVarEnv`  vectInfoVar     vi2)
1436            (vectInfoTyCon   vi1 `plusNameEnv` vectInfoTyCon   vi2)
1437            (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
1438            (vectInfoPADFun  vi1 `plusNameEnv` vectInfoPADFun  vi2)
1439            (vectInfoIso     vi1 `plusNameEnv` vectInfoIso     vi2)
1440
1441 noIfaceVectInfo :: IfaceVectInfo
1442 noIfaceVectInfo = IfaceVectInfo [] [] []
1443 \end{code}
1444
1445 %************************************************************************
1446 %*                                                                      *
1447 \subsection{Linkable stuff}
1448 %*                                                                      *
1449 %************************************************************************
1450
1451 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1452 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1453
1454 \begin{code}
1455 data Linkable = LM {
1456   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1457                                         -- (i.e. when the bytecodes were produced,
1458                                         --       or the mod date on the files)
1459   linkableModule   :: Module,           -- Should be Module, but see below
1460   linkableUnlinked :: [Unlinked]
1461  }
1462
1463 isObjectLinkable :: Linkable -> Bool
1464 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1465   where unlinked = linkableUnlinked l
1466         -- A linkable with no Unlinked's is treated as a BCO.  We can
1467         -- generate a linkable with no Unlinked's as a result of
1468         -- compiling a module in HscNothing mode, and this choice
1469         -- happens to work well with checkStability in module GHC.
1470
1471 instance Outputable Linkable where
1472    ppr (LM when_made mod unlinkeds)
1473       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1474         $$ nest 3 (ppr unlinkeds)
1475
1476 -------------------------------------------
1477 data Unlinked
1478    = DotO FilePath
1479    | DotA FilePath
1480    | DotDLL FilePath
1481    | BCOs CompiledByteCode ModBreaks
1482
1483 #ifndef GHCI
1484 data CompiledByteCode
1485 #endif
1486
1487 instance Outputable Unlinked where
1488    ppr (DotO path)   = text "DotO" <+> text path
1489    ppr (DotA path)   = text "DotA" <+> text path
1490    ppr (DotDLL path) = text "DotDLL" <+> text path
1491 #ifdef GHCI
1492    ppr (BCOs bcos _) = text "BCOs" <+> ppr bcos
1493 #else
1494    ppr (BCOs _ _)    = text "No byte code"
1495 #endif
1496
1497 isObject :: Unlinked -> Bool
1498 isObject (DotO _)   = True
1499 isObject (DotA _)   = True
1500 isObject (DotDLL _) = True
1501 isObject _          = False
1502
1503 isInterpretable :: Unlinked -> Bool
1504 isInterpretable = not . isObject
1505
1506 nameOfObject :: Unlinked -> FilePath
1507 nameOfObject (DotO fn)   = fn
1508 nameOfObject (DotA fn)   = fn
1509 nameOfObject (DotDLL fn) = fn
1510 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1511
1512 byteCodeOfObject :: Unlinked -> CompiledByteCode
1513 byteCodeOfObject (BCOs bc _) = bc
1514 byteCodeOfObject other       = pprPanic "byteCodeOfObject" (ppr other)
1515 \end{code}
1516
1517 %************************************************************************
1518 %*                                                                      *
1519 \subsection{Breakpoint Support}
1520 %*                                                                      *
1521 %************************************************************************
1522
1523 \begin{code}
1524 type BreakIndex = Int
1525
1526 -- | all the information about the breakpoints for a given module
1527 data ModBreaks
1528    = ModBreaks
1529    { modBreaks_flags :: BreakArray
1530         -- The array of flags, one per breakpoint, 
1531         -- indicating which breakpoints are enabled.
1532    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
1533         -- An array giving the source span of each breakpoint.
1534    , modBreaks_vars :: !(Array BreakIndex [OccName])
1535         -- An array giving the names of the free variables at each breakpoint.
1536    }
1537
1538 emptyModBreaks :: ModBreaks
1539 emptyModBreaks = ModBreaks
1540    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
1541          -- Todo: can we avoid this? 
1542    , modBreaks_locs = array (0,-1) []
1543    , modBreaks_vars = array (0,-1) []
1544    }
1545 \end{code}