e7df0ba787a5ee7271dc8e0274ea81537b021093
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
1
2 % (c) The University of Glasgow, 2000
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 module HscTypes ( 
8         -- * Sessions and compilation state
9         Session(..), HscEnv(..), hscEPS,
10         FinderCache, FindResult(..), ModLocationCache,
11         Target(..), TargetId(..), pprTarget, pprTargetId,
12         ModuleGraph, emptyMG,
13
14         ModDetails(..), emptyModDetails,
15         ModGuts(..), CgGuts(..), ModImports(..), ForeignStubs(..),
16
17         ModSummary(..), showModMsg, isBootSummary,
18         msHsFilePath, msHiFilePath, msObjFilePath, 
19
20         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
21         
22         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
23         hptInstances, hptRules,
24
25         ExternalPackageState(..), EpsStats(..), addEpsInStats,
26         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
27         lookupIfaceByModule, emptyModIface,
28
29         InteractiveContext(..), emptyInteractiveContext, 
30         icPrintUnqual, mkPrintUnqualified,
31
32         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
33         emptyIfaceDepCache, 
34
35         Deprecs(..), IfaceDeprecs,
36
37         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
38
39         implicitTyThings, 
40
41         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
42         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
43         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
44         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
45
46         WhetherHasOrphans, IsBootInterface, Usage(..), 
47         Dependencies(..), noDependencies,
48         NameCache(..), OrigNameCache, OrigIParamCache,
49         Avails, availsToNameSet, availName, availNames,
50         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
51         IfaceExport,
52
53         Deprecations, DeprecTxt, lookupDeprec, plusDeprecs,
54
55         PackageInstEnv, PackageRuleBase,
56
57         -- Linker stuff
58         Linkable(..), isObjectLinkable,
59         Unlinked(..), CompiledByteCode,
60         isObject, nameOfObject, isInterpretable, byteCodeOfObject
61     ) where
62
63 #include "HsVersions.h"
64
65 #ifdef GHCI
66 import ByteCodeAsm      ( CompiledByteCode )
67 #endif
68
69 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv,
70                           LocalRdrEnv, emptyLocalRdrEnv, GlobalRdrElt(..), 
71                           unQualOK, ImpDeclSpec(..), Provenance(..),
72                           ImportSpec(..), lookupGlobalRdrEnv )
73 import Name             ( Name, NamedThing, getName, nameOccName, nameModule )
74 import NameEnv
75 import NameSet  
76 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
77                           extendOccEnv )
78 import Module
79 import InstEnv          ( InstEnv, Instance )
80 import Rules            ( RuleBase )
81 import CoreSyn          ( CoreBind )
82 import Id               ( Id )
83 import Type             ( TyThing(..) )
84
85 import Class            ( Class, classSelIds, classATs, classTyCon )
86 import TyCon            ( TyCon, tyConSelIds, tyConDataCons, isNewTyCon,
87                           newTyConCo_maybe, tyConFamilyCoercion_maybe )
88 import DataCon          ( dataConImplicitIds )
89 import PrelNames        ( gHC_PRIM )
90 import Packages         ( PackageId )
91 import DynFlags         ( DynFlags(..), isOneShot, HscTarget (..) )
92 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
93 import BasicTypes       ( Version, initialVersion, IPName, 
94                           Fixity, defaultFixity, DeprecTxt )
95
96 import IfaceSyn         ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
97
98 import FiniteMap        ( FiniteMap )
99 import CoreSyn          ( CoreRule )
100 import Maybes           ( orElse, expectJust )
101 import Outputable
102 import SrcLoc           ( SrcSpan, Located )
103 import UniqFM           ( lookupUFM, eltsUFM, emptyUFM )
104 import UniqSupply       ( UniqSupply )
105 import FastString       ( FastString )
106
107 import DATA_IOREF       ( IORef, readIORef )
108 import StringBuffer     ( StringBuffer )
109 import Maybe            ( catMaybes )
110 import Time             ( ClockTime )
111 \end{code}
112
113
114 %************************************************************************
115 %*                                                                      *
116 \subsection{Compilation environment}
117 %*                                                                      *
118 %************************************************************************
119
120
121 \begin{code}
122 -- | The Session is a handle to the complete state of a compilation
123 -- session.  A compilation session consists of a set of modules
124 -- constituting the current program or library, the context for
125 -- interactive evaluation, and various caches.
126 newtype Session = Session (IORef HscEnv)
127 \end{code}
128
129 HscEnv is like Session, except that some of the fields are immutable.
130 An HscEnv is used to compile a single module from plain Haskell source
131 code (after preprocessing) to either C, assembly or C--.  Things like
132 the module graph don't change during a single compilation.
133
134 Historical note: "hsc" used to be the name of the compiler binary,
135 when there was a separate driver and compiler.  To compile a single
136 module, the driver would invoke hsc on the source code... so nowadays
137 we think of hsc as the layer of the compiler that deals with compiling
138 a single module.
139
140 \begin{code}
141 data HscEnv 
142   = HscEnv { 
143         hsc_dflags :: DynFlags,
144                 -- The dynamic flag settings
145
146         hsc_targets :: [Target],
147                 -- The targets (or roots) of the current session
148
149         hsc_mod_graph :: ModuleGraph,
150                 -- The module graph of the current session
151
152         hsc_IC :: InteractiveContext,
153                 -- The context for evaluating interactive statements
154
155         hsc_HPT    :: HomePackageTable,
156                 -- The home package table describes already-compiled
157                 -- home-packge modules, *excluding* the module we 
158                 -- are compiling right now.
159                 -- (In one-shot mode the current module is the only
160                 --  home-package module, so hsc_HPT is empty.  All other
161                 --  modules count as "external-package" modules.
162                 --  However, even in GHCi mode, hi-boot interfaces are
163                 --  demand-loadeded into the external-package table.)
164                 --
165                 -- hsc_HPT is not mutable because we only demand-load 
166                 -- external packages; the home package is eagerly 
167                 -- loaded, module by module, by the compilation manager.
168                 --      
169                 -- The HPT may contain modules compiled earlier by --make
170                 -- but not actually below the current module in the dependency
171                 -- graph.  (This changes a previous invariant: changed Jan 05.)
172         
173         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
174         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
175                 -- These are side-effected by compiling to reflect
176                 -- sucking in interface files.  They cache the state of
177                 -- external interface files, in effect.
178
179         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
180         hsc_MLC  :: {-# UNPACK #-} !(IORef ModLocationCache),
181                 -- The finder's cache.  This caches the location of modules,
182                 -- so we don't have to search the filesystem multiple times.
183
184         hsc_global_rdr_env :: GlobalRdrEnv,
185         hsc_global_type_env :: TypeEnv
186  }
187
188 hscEPS :: HscEnv -> IO ExternalPackageState
189 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
190
191 -- | A compilation target.
192 --
193 -- A target may be supplied with the actual text of the
194 -- module.  If so, use this instead of the file contents (this
195 -- is for use in an IDE where the file hasn't been saved by
196 -- the user yet).
197 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
198
199 data TargetId
200   = TargetModule ModuleName
201         -- ^ A module name: search for the file
202   | TargetFile FilePath (Maybe Phase)
203         -- ^ A filename: preprocess & parse it to find the module name.
204         -- If specified, the Phase indicates how to compile this file
205         -- (which phase to start from).  Nothing indicates the starting phase
206         -- should be determined from the suffix of the filename.
207   deriving Eq
208
209 pprTarget :: Target -> SDoc
210 pprTarget (Target id _) = pprTargetId id
211
212 pprTargetId (TargetModule m) = ppr m
213 pprTargetId (TargetFile f _) = text f
214
215 type HomePackageTable  = ModuleNameEnv HomeModInfo
216         -- Domain = modules in the home package
217         -- "home" package name cached here for convenience
218 type PackageIfaceTable = ModuleEnv ModIface
219         -- Domain = modules in the imported packages
220
221 emptyHomePackageTable  = emptyUFM
222 emptyPackageIfaceTable = emptyModuleEnv
223
224 data HomeModInfo 
225   = HomeModInfo { hm_iface    :: !ModIface,
226                   hm_details  :: !ModDetails,
227                   hm_linkable :: !(Maybe Linkable) }
228                 -- hm_linkable might be Nothing if:
229                 --   a) this is an .hs-boot module
230                 --   b) temporarily during compilation if we pruned away
231                 --      the old linkable because it was out of date.
232                 -- after a complete compilation (GHC.load), all hm_linkable
233                 -- fields in the HPT will be Just.
234                 --
235                 -- When re-linking a module (hscNoRecomp), we construct
236                 -- the HomModInfo by building a new ModDetails from the
237                 -- old ModIface (only).
238
239 -- | Find the 'ModIface' for a 'Module'
240 lookupIfaceByModule
241         :: DynFlags
242         -> HomePackageTable
243         -> PackageIfaceTable
244         -> Module
245         -> Maybe ModIface
246 lookupIfaceByModule dflags hpt pit mod
247   -- in one-shot, we don't use the HPT
248   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
249   = fmap hm_iface (lookupUFM hpt (moduleName mod))
250   | otherwise
251   = lookupModuleEnv pit mod
252   where this_pkg = thisPackage dflags
253 \end{code}
254
255
256 \begin{code}
257 hptInstances :: HscEnv -> (ModuleName -> Bool) -> [Instance]
258 -- Find all the instance declarations that are in modules imported 
259 -- by this one, directly or indirectly, and are in the Home Package Table
260 -- This ensures that we don't see instances from modules --make compiled 
261 -- before this one, but which are not below this one
262 hptInstances hsc_env want_this_module
263   = [ ispec 
264     | mod_info <- eltsUFM (hsc_HPT hsc_env)
265     , want_this_module (moduleName (mi_module (hm_iface mod_info)))
266     , ispec <- md_insts (hm_details mod_info) ]
267
268 hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
269 -- Get rules from modules "below" this one (in the dependency sense)
270 -- C.f Inst.hptInstances
271 hptRules hsc_env deps
272   | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
273   | otherwise
274   = let 
275         hpt = hsc_HPT hsc_env
276     in
277     [ rule
278     |   -- Find each non-hi-boot module below me
279       (mod, False) <- deps
280
281         -- unsavoury: when compiling the base package with --make, we
282         -- sometimes try to look up RULES for GHC.Prim.  GHC.Prim won't
283         -- be in the HPT, because we never compile it; it's in the EPT
284         -- instead.  ToDo: clean up, and remove this slightly bogus
285         -- filter:
286     , mod /= moduleName gHC_PRIM
287
288         -- Look it up in the HPT
289     , let mod_info = case lookupUFM hpt mod of
290                         Nothing -> pprPanic "hptRules" (ppr mod <+> ppr deps)
291                         Just x  -> x
292
293         -- And get its dfuns
294     , rule <- md_rules (hm_details mod_info) ]
295 \end{code}
296
297 %************************************************************************
298 %*                                                                      *
299 \subsection{The Finder cache}
300 %*                                                                      *
301 %************************************************************************
302
303 \begin{code}
304 -- | The 'FinderCache' maps home module names to the result of
305 -- searching for that module.  It records the results of searching for
306 -- modules along the search path.  On @:load@, we flush the entire
307 -- contents of this cache.
308 --
309 -- Although the @FinderCache@ range is 'FindResult' for convenience ,
310 -- in fact it will only ever contain 'Found' or 'NotFound' entries.
311 --
312 type FinderCache = ModuleNameEnv FindResult
313
314 -- | The result of searching for an imported module.
315 data FindResult
316   = Found ModLocation Module
317         -- the module was found
318   | NoPackage PackageId
319         -- the requested package was not found
320   | FoundMultiple [PackageId]
321         -- *error*: both in multiple packages
322   | PackageHidden PackageId
323         -- for an explicit source import: the package containing the module is
324         -- not exposed.
325   | ModuleHidden  PackageId
326         -- for an explicit source import: the package containing the module is
327         -- exposed, but the module itself is hidden.
328   | NotFound [FilePath] (Maybe PackageId)
329         -- the module was not found, the specified places were searched
330   | NotFoundInPackage PackageId
331         -- the module was not found in this package
332
333 -- | Cache that remembers where we found a particular module.  Contains both
334 -- home modules and package modules.  On @:load@, only home modules are
335 -- purged from this cache.
336 type ModLocationCache = ModuleEnv ModLocation
337 \end{code}
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection{Symbol tables and Module details}
342 %*                                                                      *
343 %************************************************************************
344
345 A @ModIface@ plus a @ModDetails@ summarises everything we know 
346 about a compiled module.  The @ModIface@ is the stuff *before* linking,
347 and can be written out to an interface file.  (The @ModDetails@ is after 
348 linking; it is the "linked" form of the mi_decls field.)
349
350 When we *read* an interface file, we also construct a @ModIface@ from it,
351 except that the mi_decls part is empty; when reading we consolidate
352 the declarations into a single indexed map in the @PersistentRenamerState@.
353
354 \begin{code}
355 data ModIface 
356    = ModIface {
357         mi_module   :: !Module,
358         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
359
360         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
361         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
362
363         mi_deps     :: Dependencies,
364                 -- This is consulted for directly-imported modules,
365                 -- but not for anything else (hence lazy)
366
367                 -- Usages; kept sorted so that it's easy to decide
368                 -- whether to write a new iface file (changing usages
369                 -- doesn't affect the version of this module)
370         mi_usages   :: [Usage],
371                 -- NOT STRICT!  we read this field lazily from the interface file
372                 -- It is *only* consulted by the recompilation checker
373
374                 -- Exports
375                 -- Kept sorted by (mod,occ), to make version comparisons easier
376         mi_exports  :: ![IfaceExport],
377         mi_exp_vers :: !Version,        -- Version number of export list
378
379                 -- Fixities
380         mi_fixities :: [(OccName,Fixity)],
381                 -- NOT STRICT!  we read this field lazily from the interface file
382
383                 -- Deprecations
384         mi_deprecs  :: IfaceDeprecs,
385                 -- NOT STRICT!  we read this field lazily from the interface file
386
387                 -- Type, class and variable declarations
388                 -- The version of an Id changes if its fixity or deprecations change
389                 --      (as well as its type of course)
390                 -- Ditto data constructors, class operations, except that 
391                 -- the version of the parent class/tycon changes
392         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
393
394         mi_globals  :: !(Maybe GlobalRdrEnv),
395                 -- Binds all the things defined at the top level in
396                 -- the *original source* code for this module. which
397                 -- is NOT the same as mi_exports, nor mi_decls (which
398                 -- may contains declarations for things not actually
399                 -- defined by the user).  Used for GHCi and for inspecting
400                 -- the contents of modules via the GHC API only.
401                 --
402                 -- (We need the source file to figure out the
403                 -- top-level environment, if we didn't compile this module
404                 -- from source then this field contains Nothing).
405                 --
406                 -- Strictly speaking this field should live in the
407                 -- HomeModInfo, but that leads to more plumbing.
408
409                 -- Instance declarations and rules
410         mi_insts     :: [IfaceInst],    -- Sorted
411         mi_rules     :: [IfaceRule],    -- Sorted
412         mi_rule_vers :: !Version,       -- Version number for rules and instances combined
413
414                 -- Cached environments for easy lookup
415                 -- These are computed (lazily) from other fields
416                 -- and are not put into the interface file
417         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
418         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
419         mi_ver_fn  :: OccName -> Maybe Version  -- Cached lookup for mi_decls
420                         -- The Nothing in mi_ver_fn means that the thing
421                         -- isn't in decls. It's useful to know that when
422                         -- seeing if we are up to date wrt the old interface
423      }
424
425 -- Should be able to construct ModDetails from mi_decls in ModIface
426 data ModDetails
427    = ModDetails {
428         -- The next three fields are created by the typechecker
429         md_exports  :: NameSet,
430         md_types    :: !TypeEnv,
431         md_insts    :: ![Instance],     -- Dfun-ids for the instances in this module
432         md_rules    :: ![CoreRule]      -- Domain may include Ids from other modules
433      }
434
435 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
436                                md_exports = emptyNameSet,
437                                md_insts = [],
438                                md_rules = [] }
439
440 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
441 -- There is only one ModGuts at any time, the one for the module
442 -- being compiled right now.  Once it is compiled, a ModIface and 
443 -- ModDetails are extracted and the ModGuts is dicarded.
444
445 data ModGuts
446   = ModGuts {
447         mg_module   :: !Module,
448         mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
449         mg_exports  :: !NameSet,        -- What it exports
450         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
451         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
452                                         --      generate initialisation code
453         mg_usages   :: ![Usage],        -- Version info for what it needed
454
455         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
456         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
457         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
458
459         mg_types    :: !TypeEnv,
460         mg_insts    :: ![Instance],     -- Instances 
461         mg_rules    :: ![CoreRule],     -- Rules from this module
462         mg_binds    :: ![CoreBind],     -- Bindings for this module
463         mg_foreign  :: !ForeignStubs
464     }
465
466 -- The ModGuts takes on several slightly different forms:
467 --
468 -- After simplification, the following fields change slightly:
469 --      mg_rules        Orphan rules only (local ones now attached to binds)
470 --      mg_binds        With rules attached
471
472
473 ---------------------------------------------------------
474 -- The Tidy pass forks the information about this module: 
475 --      * one lot goes to interface file generation (ModIface)
476 --        and later compilations (ModDetails)
477 --      * the other lot goes to code generation (CgGuts)
478 data CgGuts 
479   = CgGuts {
480         cg_module   :: !Module,
481
482         cg_tycons   :: [TyCon],
483                 -- Algebraic data types (including ones that started
484                 -- life as classes); generate constructors and info
485                 -- tables Includes newtypes, just for the benefit of
486                 -- External Core
487
488         cg_binds    :: [CoreBind],
489                 -- The tidied main bindings, including
490                 -- previously-implicit bindings for record and class
491                 -- selectors, and data construtor wrappers.  But *not*
492                 -- data constructor workers; reason: we we regard them
493                 -- as part of the code-gen of tycons
494
495         cg_dir_imps :: ![Module],
496                 -- Directly-imported modules; used to generate
497                 -- initialisation code
498
499         cg_foreign  :: !ForeignStubs,   
500         cg_dep_pkgs :: ![PackageId]     -- Used to generate #includes for C code gen
501     }
502
503 -----------------------------------
504 data ModImports
505   = ModImports {
506         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
507                                                 -- Boolean is true if we imported the whole
508                                                 --      module (apart, perhaps, from hiding some)
509         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
510                                                 --      directly or indirectly
511         imp_home_names :: !NameSet              -- Home package things on which we depend,
512                                                 --      directly or indirectly
513     }
514
515 -----------------------------------
516 data ForeignStubs = NoStubs
517                   | ForeignStubs
518                         SDoc            -- Header file prototypes for
519                                         --      "foreign exported" functions
520                         SDoc            -- C stubs to use when calling
521                                         --      "foreign exported" functions
522                         [FastString]    -- Headers that need to be included
523                                         --      into C code generated for this module
524                         [Id]            -- Foreign-exported binders
525                                         --      we have to generate code to register these
526
527 \end{code}
528
529 \begin{code}
530 emptyModIface :: Module -> ModIface
531 emptyModIface mod
532   = ModIface { mi_module   = mod,
533                mi_mod_vers = initialVersion,
534                mi_orphan   = False,
535                mi_boot     = False,
536                mi_deps     = noDependencies,
537                mi_usages   = [],
538                mi_exports  = [],
539                mi_exp_vers = initialVersion,
540                mi_fixities = [],
541                mi_deprecs  = NoDeprecs,
542                mi_insts = [],
543                mi_rules = [],
544                mi_decls = [],
545                mi_globals  = Nothing,
546                mi_rule_vers = initialVersion,
547                mi_dep_fn = emptyIfaceDepCache,
548                mi_fix_fn = emptyIfaceFixCache,
549                mi_ver_fn = emptyIfaceVerCache
550     }           
551 \end{code}
552
553
554 %************************************************************************
555 %*                                                                      *
556 \subsection{The interactive context}
557 %*                                                                      *
558 %************************************************************************
559
560 \begin{code}
561 data InteractiveContext 
562   = InteractiveContext { 
563         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
564                                         -- these modules
565
566         ic_exports :: [Module],         -- Include just the exports of these
567                                         -- modules
568
569         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
570                                         -- ic_toplev_scope and ic_exports
571
572         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
573                                         -- during interaction
574
575         ic_type_env :: TypeEnv          -- Ditto for types
576     }
577
578 emptyInteractiveContext
579   = InteractiveContext { ic_toplev_scope = [],
580                          ic_exports = [],
581                          ic_rn_gbl_env = emptyGlobalRdrEnv,
582                          ic_rn_local_env = emptyLocalRdrEnv,
583                          ic_type_env = emptyTypeEnv }
584
585 icPrintUnqual :: InteractiveContext -> PrintUnqualified
586 icPrintUnqual ictxt = mkPrintUnqualified (ic_rn_gbl_env ictxt)
587 \end{code}
588
589 %************************************************************************
590 %*                                                                      *
591         Building a PrintUnqualified             
592 %*                                                                      *
593 %************************************************************************
594
595 \begin{code}
596 mkPrintUnqualified :: GlobalRdrEnv -> PrintUnqualified
597 mkPrintUnqualified env = (qual_name, qual_mod)
598   where
599   qual_name mod occ
600         | null gres = Just (moduleName mod)
601                 -- it isn't in scope at all, this probably shouldn't happen,
602                 -- but we'll qualify it by the original module anyway.
603         | any unQualOK gres = Nothing
604         | (Imported is : _) <- map gre_prov gres, (idecl : _) <- is
605           = Just (is_as (is_decl idecl))
606         | otherwise = panic "mkPrintUnqualified" 
607       where
608         gres  = [ gre | gre <- lookupGlobalRdrEnv env occ,
609                         nameModule (gre_name gre) == mod ]
610
611   qual_mod mod = Nothing       -- For now...
612 \end{code}
613
614
615 %************************************************************************
616 %*                                                                      *
617                 TyThing
618 %*                                                                      *
619 %************************************************************************
620
621 \begin{code}
622 implicitTyThings :: TyThing -> [TyThing]
623 -- If you change this, make sure you change LoadIface.ifaceDeclSubBndrs in sync
624
625 implicitTyThings (AnId id)   = []
626
627         -- For type constructors, add the data cons (and their extras),
628         -- and the selectors and generic-programming Ids too
629         --
630         -- Newtypes don't have a worker Id, so don't generate that?
631 implicitTyThings (ATyCon tc) = implicitCoTyCon tc ++
632                                map AnId (tyConSelIds tc) ++ 
633                                concatMap (extras_plus . ADataCon) 
634                                          (tyConDataCons tc)
635                      
636         -- For classes, add the class TyCon too (and its extras)
637         -- and the class selector Ids and the associated types (they don't
638         -- have extras as these are only the family decls)
639 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
640                                map ATyCon (classATs cl) ++
641                                extras_plus (ATyCon (classTyCon cl))
642
643         -- For data cons add the worker and wrapper (if any)
644 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
645
646         -- For newtypes and indexed data types, add the implicit coercion tycon
647 implicitCoTyCon tc 
648   = map ATyCon . catMaybes $ [newTyConCo_maybe tc, 
649                               tyConFamilyCoercion_maybe tc]
650
651 extras_plus thing = thing : implicitTyThings thing
652
653 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
654 extendTypeEnvWithIds env ids
655   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
656 \end{code}
657
658 %************************************************************************
659 %*                                                                      *
660                 TypeEnv
661 %*                                                                      *
662 %************************************************************************
663
664 \begin{code}
665 type TypeEnv = NameEnv TyThing
666
667 emptyTypeEnv   :: TypeEnv
668 typeEnvElts    :: TypeEnv -> [TyThing]
669 typeEnvClasses :: TypeEnv -> [Class]
670 typeEnvTyCons  :: TypeEnv -> [TyCon]
671 typeEnvIds     :: TypeEnv -> [Id]
672 lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
673
674 emptyTypeEnv       = emptyNameEnv
675 typeEnvElts    env = nameEnvElts env
676 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
677 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
678 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
679
680 mkTypeEnv :: [TyThing] -> TypeEnv
681 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
682                 
683 lookupTypeEnv = lookupNameEnv
684
685 -- Extend the type environment
686 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
687 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
688
689 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
690 extendTypeEnvList env things = foldl extendTypeEnv env things
691 \end{code}
692
693 \begin{code}
694 lookupType :: DynFlags
695            -> HomePackageTable
696            -> PackageTypeEnv
697            -> Name
698            -> Maybe TyThing
699
700 lookupType dflags hpt pte name
701   -- in one-shot, we don't use the HPT
702   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
703   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
704        lookupNameEnv (md_types (hm_details hm)) name
705   | otherwise
706   = lookupNameEnv pte name
707   where mod = nameModule name
708         this_pkg = thisPackage dflags
709 \end{code}
710
711
712 \begin{code}
713 tyThingTyCon (ATyCon tc) = tc
714 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
715
716 tyThingClass (AClass cls) = cls
717 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
718
719 tyThingDataCon (ADataCon dc) = dc
720 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
721
722 tyThingId (AnId id) = id
723 tyThingId other     = pprPanic "tyThingId" (ppr other)
724 \end{code}
725
726 %************************************************************************
727 %*                                                                      *
728 \subsection{Auxiliary types}
729 %*                                                                      *
730 %************************************************************************
731
732 These types are defined here because they are mentioned in ModDetails,
733 but they are mostly elaborated elsewhere
734
735 \begin{code}
736 mkIfaceVerCache :: [(Version,IfaceDecl)] -> OccName -> Maybe Version
737 mkIfaceVerCache pairs 
738   = \occ -> lookupOccEnv env occ
739   where
740     env = foldl add emptyOccEnv pairs
741     add env (v,d) = extendOccEnv env (ifName d) v
742
743 emptyIfaceVerCache :: OccName -> Maybe Version
744 emptyIfaceVerCache occ = Nothing
745
746 ------------------ Deprecations -------------------------
747 data Deprecs a
748   = NoDeprecs
749   | DeprecAll DeprecTxt -- Whole module deprecated
750   | DeprecSome a        -- Some specific things deprecated
751   deriving( Eq )
752
753 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
754 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
755         -- Keep the OccName so we can flatten the NameEnv to
756         -- get an IfaceDeprecs from a Deprecations
757         -- Only an OccName is needed, because a deprecation always
758         -- applies to things defined in the module in which the
759         -- deprecation appears.
760
761 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
762 mkIfaceDepCache NoDeprecs         = \n -> Nothing
763 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
764 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
765
766 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
767 emptyIfaceDepCache n = Nothing
768
769 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
770 lookupDeprec NoDeprecs        name = Nothing
771 lookupDeprec (DeprecAll  txt) name = Just txt
772 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
773                                             Just (_, txt) -> Just txt
774                                             Nothing       -> Nothing
775
776 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
777 plusDeprecs d NoDeprecs = d
778 plusDeprecs NoDeprecs d = d
779 plusDeprecs d (DeprecAll t) = DeprecAll t
780 plusDeprecs (DeprecAll t) d = DeprecAll t
781 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
782 \end{code}
783
784
785 \begin{code}
786 type Avails       = [AvailInfo]
787 type AvailInfo    = GenAvailInfo Name
788 type RdrAvailInfo = GenAvailInfo OccName
789
790 data GenAvailInfo name  = Avail name     -- An ordinary identifier
791                         | AvailTC name   -- The name of the type or class
792                                   [name] -- The available pieces of type/class.
793                                          -- NB: If the type or class is itself
794                                          -- to be in scope, it must be in this list.
795                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
796                         deriving( Eq )
797                         -- Equality used when deciding if the interface has changed
798
799 type IfaceExport = (Module, [GenAvailInfo OccName])
800
801 availsToNameSet :: [AvailInfo] -> NameSet
802 availsToNameSet avails = foldl add emptyNameSet avails
803                        where
804                          add set avail = addListToNameSet set (availNames avail)
805
806 availName :: GenAvailInfo name -> name
807 availName (Avail n)     = n
808 availName (AvailTC n _) = n
809
810 availNames :: GenAvailInfo name -> [name]
811 availNames (Avail n)      = [n]
812 availNames (AvailTC n ns) = ns
813
814 instance Outputable n => Outputable (GenAvailInfo n) where
815    ppr = pprAvail
816
817 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
818 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
819                                         []  -> empty
820                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
821
822 pprAvail (Avail n) = ppr n
823 \end{code}
824
825 \begin{code}
826 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
827 mkIfaceFixCache pairs 
828   = \n -> lookupOccEnv env n `orElse` defaultFixity
829   where
830    env = mkOccEnv pairs
831
832 emptyIfaceFixCache :: OccName -> Fixity
833 emptyIfaceFixCache n = defaultFixity
834
835 -- This fixity environment is for source code only
836 type FixityEnv = NameEnv FixItem
837
838 -- We keep the OccName in the range so that we can generate an interface from it
839 data FixItem = FixItem OccName Fixity SrcSpan
840
841 instance Outputable FixItem where
842   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
843
844 emptyFixityEnv :: FixityEnv
845 emptyFixityEnv = emptyNameEnv
846
847 lookupFixity :: FixityEnv -> Name -> Fixity
848 lookupFixity env n = case lookupNameEnv env n of
849                         Just (FixItem _ fix _) -> fix
850                         Nothing                -> defaultFixity
851 \end{code}
852
853
854 %************************************************************************
855 %*                                                                      *
856 \subsection{WhatsImported}
857 %*                                                                      *
858 %************************************************************************
859
860 \begin{code}
861 type WhetherHasOrphans   = Bool
862         -- An "orphan" is 
863         --      * an instance decl in a module other than the defn module for 
864         --              one of the tycons or classes in the instance head
865         --      * a transformation rule in a module other than the one defining
866         --              the function in the head of the rule.
867
868 type IsBootInterface = Bool
869
870 -- Dependency info about modules and packages below this one
871 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
872 --
873 -- Invariant: the dependencies of a module M never includes M
874 -- Invariant: the lists are unordered, with no duplicates
875 data Dependencies
876   = Deps { dep_mods  :: [(ModuleName,IsBootInterface)], -- Home-package module dependencies
877            dep_pkgs  :: [PackageId],                    -- External package dependencies
878            dep_orphs :: [Module] }                      -- Orphan modules (whether home or external pkg)
879   deriving( Eq )
880         -- Equality used only for old/new comparison in MkIface.addVersionInfo
881
882 noDependencies :: Dependencies
883 noDependencies = Deps [] [] []
884           
885 data Usage
886   = Usage { usg_name     :: ModuleName,                 -- Name of the module
887             usg_mod      :: Version,                    -- Module version
888             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
889             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
890             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
891                                                         -- modules this will always be initialVersion)
892     }       deriving( Eq )
893         -- This type doesn't let you say "I imported f but none of the rules in
894         -- the module". If you use anything in the module you get its rule version
895         -- So if the rules change, you'll recompile, even if you don't use them.
896         -- This is easy to implement, and it's safer: you might not have used the rules last
897         -- time round, but if someone has added a new rule you might need it this time
898
899         -- The export list field is (Just v) if we depend on the export list:
900         --      i.e. we imported the module directly, whether or not we
901         --           enumerated the things we imported, or just imported everything
902         -- We need to recompile if M's exports change, because 
903         -- if the import was    import M,       we might now have a name clash in the 
904         --                                      importing module.
905         -- if the import was    import M(x)     M might no longer export x
906         -- The only way we don't depend on the export list is if we have
907         --                      import M()
908         -- And of course, for modules that aren't imported directly we don't
909         -- depend on their export lists
910 \end{code}
911
912
913 %************************************************************************
914 %*                                                                      *
915                 The External Package State
916 %*                                                                      *
917 %************************************************************************
918
919 \begin{code}
920 type PackageTypeEnv  = TypeEnv
921 type PackageRuleBase = RuleBase
922 type PackageInstEnv  = InstEnv
923
924 data ExternalPackageState
925   = EPS {
926         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
927                 -- In OneShot mode (only), home-package modules
928                 -- accumulate in the external package state, and are
929                 -- sucked in lazily.  For these home-pkg modules
930                 -- (only) we need to record which are boot modules.
931                 -- We set this field after loading all the
932                 -- explicitly-imported interfaces, but before doing
933                 -- anything else
934                 --
935                 -- The ModuleName part is not necessary, but it's useful for
936                 -- debug prints, and it's convenient because this field comes
937                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
938
939         eps_PIT :: !PackageIfaceTable,
940                 -- The ModuleIFaces for modules in external packages
941                 -- whose interfaces we have opened
942                 -- The declarations in these interface files are held in
943                 -- eps_decls, eps_inst_env, eps_rules (below), not in the 
944                 -- mi_decls fields of the iPIT.  
945                 -- What _is_ in the iPIT is:
946                 --      * The Module 
947                 --      * Version info
948                 --      * Its exports
949                 --      * Fixities
950                 --      * Deprecations
951
952         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
953
954         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
955                                                 --   all the external-package modules
956         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
957
958         eps_stats :: !EpsStats
959   }
960
961 -- "In" means read from iface files
962 -- "Out" means actually sucked in and type-checked
963 data EpsStats = EpsStats { n_ifaces_in
964                          , n_decls_in, n_decls_out 
965                          , n_rules_in, n_rules_out
966                          , n_insts_in, n_insts_out :: !Int }
967
968 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
969 -- Add stats for one newly-read interface
970 addEpsInStats stats n_decls n_insts n_rules
971   = stats { n_ifaces_in = n_ifaces_in stats + 1
972           , n_decls_in  = n_decls_in stats + n_decls
973           , n_insts_in  = n_insts_in stats + n_insts
974           , n_rules_in  = n_rules_in stats + n_rules }
975 \end{code}
976
977 The NameCache makes sure that there is just one Unique assigned for
978 each original name; i.e. (module-name, occ-name) pair.  The Name is
979 always stored as a Global, and has the SrcLoc of its binding location.
980 Actually that's not quite right.  When we first encounter the original
981 name, we might not be at its binding site (e.g. we are reading an
982 interface file); so we give it 'noSrcLoc' then.  Later, when we find
983 its binding site, we fix it up.
984
985 \begin{code}
986 data NameCache
987  = NameCache {  nsUniqs :: UniqSupply,
988                 -- Supply of uniques
989                 nsNames :: OrigNameCache,
990                 -- Ensures that one original name gets one unique
991                 nsIPs   :: OrigIParamCache
992                 -- Ensures that one implicit parameter name gets one unique
993    }
994
995 type OrigNameCache   = ModuleEnv (OccEnv Name)
996 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
997 \end{code}
998
999
1000
1001 %************************************************************************
1002 %*                                                                      *
1003                 The module graph and ModSummary type
1004         A ModSummary is a node in the compilation manager's
1005         dependency graph, and it's also passed to hscMain
1006 %*                                                                      *
1007 %************************************************************************
1008
1009 A ModuleGraph contains all the nodes from the home package (only).  
1010 There will be a node for each source module, plus a node for each hi-boot
1011 module.
1012
1013 \begin{code}
1014 type ModuleGraph = [ModSummary]  -- The module graph, 
1015                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
1016
1017 emptyMG :: ModuleGraph
1018 emptyMG = []
1019
1020 -- The nodes of the module graph are
1021 --      EITHER a regular Haskell source module
1022 --      OR     a hi-boot source module
1023
1024 data ModSummary
1025    = ModSummary {
1026         ms_mod       :: Module,                 -- Identity of the module
1027         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
1028         ms_location  :: ModLocation,            -- Location
1029         ms_hs_date   :: ClockTime,              -- Timestamp of source file
1030         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
1031         ms_srcimps   :: [Located ModuleName],   -- Source imports
1032         ms_imps      :: [Located ModuleName],   -- Non-source imports
1033         ms_hspp_file :: FilePath,               -- Filename of preprocessed source.
1034         ms_hspp_opts :: DynFlags,               -- Cached flags from OPTIONS, INCLUDE
1035                                                 -- and LANGUAGE pragmas.
1036         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
1037      }
1038
1039 -- The ModLocation contains both the original source filename and the
1040 -- filename of the cleaned-up source file after all preprocessing has been
1041 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1042 -- all files anyway, and there's no point in doing this twice -- just 
1043 -- park the result in a temp file, put the name of it in the location,
1044 -- and let @compile@ read from that file on the way back up.
1045
1046 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1047 -- the ms_hs_date and imports can, of course, change
1048
1049 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1050 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1051 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1052 msObjFilePath ms = ml_obj_file (ms_location ms)
1053
1054 isBootSummary :: ModSummary -> Bool
1055 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1056
1057 instance Outputable ModSummary where
1058    ppr ms
1059       = sep [text "ModSummary {",
1060              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1061                           text "ms_mod =" <+> ppr (ms_mod ms) 
1062                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1063                           text "ms_imps =" <+> ppr (ms_imps ms),
1064                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1065              char '}'
1066             ]
1067
1068 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1069 showModMsg target recomp mod_summary
1070   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1071                     char '(', text (msHsFilePath mod_summary) <> comma,
1072                     case target of
1073                       HscInterpreted | recomp
1074                                  -> text "interpreted"
1075                       HscNothing -> text "nothing"
1076                       _other     -> text (msObjFilePath mod_summary),
1077                     char ')'])
1078  where 
1079     mod     = moduleName (ms_mod mod_summary)
1080     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1081 \end{code}
1082
1083
1084 %************************************************************************
1085 %*                                                                      *
1086 \subsection{Linkable stuff}
1087 %*                                                                      *
1088 %************************************************************************
1089
1090 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1091 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1092
1093 \begin{code}
1094 data Linkable = LM {
1095   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1096                                         -- (i.e. when the bytecodes were produced,
1097                                         --       or the mod date on the files)
1098   linkableModule   :: Module,           -- Should be Module, but see below
1099   linkableUnlinked :: [Unlinked]
1100  }
1101
1102 isObjectLinkable :: Linkable -> Bool
1103 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1104   where unlinked = linkableUnlinked l
1105         -- A linkable with no Unlinked's is treated as a BCO.  We can
1106         -- generate a linkable with no Unlinked's as a result of
1107         -- compiling a module in HscNothing mode, and this choice
1108         -- happens to work well with checkStability in module GHC.
1109
1110 instance Outputable Linkable where
1111    ppr (LM when_made mod unlinkeds)
1112       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1113         $$ nest 3 (ppr unlinkeds)
1114
1115 -------------------------------------------
1116 data Unlinked
1117    = DotO FilePath
1118    | DotA FilePath
1119    | DotDLL FilePath
1120    | BCOs CompiledByteCode
1121
1122 #ifndef GHCI
1123 data CompiledByteCode = NoByteCode
1124 #endif
1125
1126 instance Outputable Unlinked where
1127    ppr (DotO path)   = text "DotO" <+> text path
1128    ppr (DotA path)   = text "DotA" <+> text path
1129    ppr (DotDLL path) = text "DotDLL" <+> text path
1130 #ifdef GHCI
1131    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1132 #else
1133    ppr (BCOs bcos)   = text "No byte code"
1134 #endif
1135
1136 isObject (DotO _)   = True
1137 isObject (DotA _)   = True
1138 isObject (DotDLL _) = True
1139 isObject _          = False
1140
1141 isInterpretable = not . isObject
1142
1143 nameOfObject (DotO fn)   = fn
1144 nameOfObject (DotA fn)   = fn
1145 nameOfObject (DotDLL fn) = fn
1146 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1147
1148 byteCodeOfObject (BCOs bc) = bc
1149 byteCodeOfObject other     = pprPanic "byteCodeOfObject" (ppr other)
1150 \end{code}
1151
1152
1153