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