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