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