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