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