[project @ 2002-10-24 14:17:46 by simonpj]
[ghc-hetmet.git] / ghc / 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         HscEnv(..), 
9         GhciMode(..),
10
11         ModDetails(..), ModIface(..), 
12         ModGuts(..), ModImports(..), ForeignStubs(..),
13         ParsedIface(..), IfaceDeprecs,
14
15         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
16
17         ExternalPackageState(..), 
18         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
19         lookupIface, lookupIfaceByModName, moduleNameToModule,
20         emptyModIface,
21
22         InteractiveContext(..), emptyInteractiveContext, icPrintUnqual,
23
24         IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts,
25
26         VersionInfo(..), initialVersionInfo, lookupVersion,
27         FixityEnv, lookupFixity, collectFixities, emptyFixityEnv,
28
29         TyThing(..), isTyClThing, implicitTyThingIds,
30
31         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
32         extendTypeEnvList, extendTypeEnvWithIds,
33         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
34
35         WhetherHasOrphans, IsBootInterface, DeclsMap, Usage(..), Dependencies, 
36         IfaceInsts, IfaceRules, GatedDecl, GatedDecls, GateFn, 
37         NameCache(..), OrigNameCache, OrigIParamCache,
38         Avails, availsToNameSet, availName, availNames,
39         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
40         ExportItem, RdrExportItem,
41
42         PersistentCompilerState(..),
43
44         Deprecations(..), lookupDeprec, plusDeprecs,
45
46         InstEnv, ClsInstEnv, DFunId,
47         PackageInstEnv, PackageRuleBase,
48
49         GlobalRdrEnv, GlobalRdrElt(..), emptyGlobalRdrEnv, pprGlobalRdrEnv,
50         LocalRdrEnv, extendLocalRdrEnv, isLocalGRE, unQualInScope,
51         
52         -- Linker stuff
53         Linkable(..), isObjectLinkable,
54         Unlinked(..), CompiledByteCode,
55         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
56
57         -- Provenance
58         Provenance(..), ImportReason(..), 
59         pprNameProvenance, hasBetterProv
60
61     ) where
62
63 #include "HsVersions.h"
64
65 #ifdef GHCI
66 import ByteCodeAsm      ( CompiledByteCode )
67 #endif
68
69 import RdrName          ( RdrName, mkRdrUnqual, 
70                           RdrNameEnv, addListToRdrEnv, foldRdrEnv, isUnqual,
71                           rdrEnvToList, emptyRdrEnv )
72 import Name             ( Name, NamedThing, getName, nameOccName, nameModule, nameSrcLoc )
73 import NameEnv
74 import NameSet  
75 import OccName          ( OccName )
76 import Module
77 import InstEnv          ( InstEnv, ClsInstEnv, DFunId )
78 import Rules            ( RuleBase )
79 import CoreSyn          ( CoreBind )
80 import Id               ( Id )
81 import Class            ( Class, classSelIds )
82 import TyCon            ( TyCon, isNewTyCon, tyConGenIds, tyConSelIds, tyConDataCons_maybe )
83 import Type             ( TyThing(..), isTyClThing )
84 import DataCon          ( dataConWorkId, dataConWrapId )
85 import Packages         ( PackageName, basePackage )
86 import CmdLineOpts      ( DynFlags )
87
88 import BasicTypes       ( Version, initialVersion, IPName,
89                           Fixity, FixitySig(..), defaultFixity )
90
91 import HsSyn            ( DeprecTxt, TyClDecl, InstDecl, RuleDecl,
92                           tyClDeclName, ifaceRuleDeclName, tyClDeclNames,
93                           instDeclDFun )
94 import RnHsSyn          ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
95
96 import CoreSyn          ( IdCoreRule )
97 import PrelNames        ( isBuiltInSyntaxName )
98
99 import FiniteMap
100 import Bag              ( Bag )
101 import Maybes           ( orElse )
102 import Outputable
103 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
104 import Util             ( thenCmp, sortLt )
105 import UniqSupply       ( UniqSupply )
106 import Maybe            ( fromJust )
107 import FastString       ( FastString )
108
109 import Time             ( ClockTime )
110 \end{code}
111
112
113 %************************************************************************
114 %*                                                                      *
115 \subsection{Compilation environment}
116 %*                                                                      *
117 %************************************************************************
118
119 The HscEnv gives the environment in which to compile a chunk of code.
120
121 \begin{code}
122 data HscEnv = HscEnv { hsc_mode   :: GhciMode,
123                        hsc_dflags :: DynFlags,
124                        hsc_HPT    :: HomePackageTable }
125 \end{code}
126
127 The GhciMode is self-explanatory:
128
129 \begin{code}
130 data GhciMode = Batch | Interactive | OneShot 
131               deriving Eq
132 \end{code}
133
134 \begin{code}
135 type HomePackageTable  = ModuleEnv HomeModInfo  -- Domain = modules in the home package
136 type PackageIfaceTable = ModuleEnv ModIface     -- Domain = modules in the imported packages
137
138 emptyHomePackageTable  = emptyModuleEnv
139 emptyPackageIfaceTable = emptyModuleEnv
140
141 data HomeModInfo = HomeModInfo { hm_iface    :: ModIface,
142                                  hm_details  :: ModDetails,
143                                  hm_linkable :: Linkable }
144 \end{code}
145
146 Simple lookups in the symbol table.
147
148 \begin{code}
149 lookupIface :: HomePackageTable -> PackageIfaceTable -> Name -> Maybe ModIface
150 -- We often have two IfaceTables, and want to do a lookup
151 lookupIface hpt pit name
152   = case lookupModuleEnv hpt mod of
153         Just mod_info -> Just (hm_iface mod_info)
154         Nothing       -> lookupModuleEnv pit mod
155   where
156     mod = nameModule name
157
158 lookupIfaceByModName :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
159 -- We often have two IfaceTables, and want to do a lookup
160 lookupIfaceByModName hpt pit mod
161   = case lookupModuleEnvByName hpt mod of
162         Just mod_info -> Just (hm_iface mod_info)
163         Nothing       -> lookupModuleEnvByName pit mod
164 \end{code}
165
166 \begin{code}
167 -- Use instead of Finder.findModule if possible: this way doesn't
168 -- require filesystem operations, and it is guaranteed not to fail
169 -- when the IfaceTables are properly populated (i.e. after the renamer).
170 moduleNameToModule :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Module
171 moduleNameToModule hpt pit mod 
172    = mi_module (fromJust (lookupIfaceByModName hpt pit mod))
173 \end{code}
174
175
176 %************************************************************************
177 %*                                                                      *
178 \subsection{Symbol tables and Module details}
179 %*                                                                      *
180 %************************************************************************
181
182 A @ModIface@ plus a @ModDetails@ summarises everything we know 
183 about a compiled module.  The @ModIface@ is the stuff *before* linking,
184 and can be written out to an interface file.  (The @ModDetails@ is after 
185 linking; it is the "linked" form of the mi_decls field.)
186
187 When we *read* an interface file, we also construct a @ModIface@ from it,
188 except that the mi_decls part is empty; when reading we consolidate
189 the declarations into a single indexed map in the @PersistentRenamerState@.
190
191 \begin{code}
192 data ModIface 
193    = ModIface {
194         mi_module   :: !Module,
195         mi_package  :: !PackageName,        -- Which package the module comes from
196         mi_version  :: !VersionInfo,        -- Version info for everything in this module
197         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
198         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
199
200         mi_deps     :: Dependencies,
201                 -- This is consulted for directly-imported modules, but
202                 -- not for anything else
203
204         mi_usages   :: [Usage Name],
205                 -- Usages; kept sorted so that it's easy to decide
206                 -- whether to write a new iface file (changing usages
207                 -- doesn't affect the version of this module)
208                 -- NOT STRICT!  we read this field lazily from the interface file
209                 -- It is *only* consulted by the recompilation checker
210
211         mi_exports  :: ![ExportItem],
212                 -- What it exports Kept sorted by (mod,occ), to make
213                 -- version comparisons easier
214
215         mi_globals  :: !(Maybe GlobalRdrEnv),
216                 -- Its top level environment or Nothing if we read this
217                 -- interface from an interface file.  (We need the source
218                 -- file to figure out the top-level environment.)
219
220         mi_fixities :: !FixityEnv,          -- Fixities
221         mi_deprecs  :: Deprecations,        -- Deprecations
222                 -- NOT STRICT!  we read this field lazilly from the interface file
223
224         mi_decls    :: IfaceDecls           -- The RnDecls form of ModDetails
225                 -- NOT STRICT!  we fill this field with _|_ sometimes
226      }
227
228 -- Should be able to construct ModDetails from mi_decls in ModIface
229 data ModDetails
230    = ModDetails {
231         -- The next three fields are created by the typechecker
232         md_types    :: !TypeEnv,
233         md_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
234         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
235      }
236
237 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
238 -- There is only one ModGuts at any time, the one for the module
239 -- being compiled right now.  Once it is compiled, a ModIface and 
240 -- ModDetails are extracted and the ModGuts is dicarded.
241
242 data ModGuts
243   = ModGuts {
244         mg_module   :: !Module,
245         mg_exports  :: !Avails,         -- What it exports
246         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
247         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
248                                         --      generate initialisation code
249         mg_usages   :: ![Usage Name],   -- Version info for what it needed
250
251         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
252         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
253         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
254
255         mg_types    :: !TypeEnv,
256         mg_insts    :: ![DFunId],       -- Instances 
257         mg_rules    :: ![IdCoreRule],   -- Rules from this module
258         mg_binds    :: ![CoreBind],     -- Bindings for this module
259         mg_foreign  :: !ForeignStubs
260     }
261
262 -- The ModGuts takes on several slightly different forms:
263 --
264 -- After simplification, the following fields change slightly:
265 --      mg_rules        Orphan rules only (local ones now attached to binds)
266 --      mg_binds        With rules attached
267 --
268 -- After CoreTidy, the following fields change slightly:
269 --      mg_types        Now contains Ids as well, replete with final IdInfo
270 --                         The Ids are only the ones that are visible from
271 --                         importing modules.  Without -O that means only
272 --                         exported Ids, but with -O importing modules may
273 --                         see ids mentioned in unfoldings of exported Ids
274 --
275 --      mg_insts        Same DFunIds as before, but with final IdInfo,
276 --                         and the unique might have changed; remember that
277 --                         CoreTidy links up the uniques of old and new versions
278 --
279 --      mg_rules        All rules for exported things, substituted with final Ids
280 --
281 --      mg_binds        Tidied
282
283
284
285 data ModImports
286   = ModImports {
287         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
288                                                 -- Boolean is true if we imported the whole
289                                                 --      module (apart, perhaps, from hiding some)
290         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
291                                                 --      directly or indirectly
292         imp_home_names :: !NameSet              -- Home package things on which we depend,
293                                                 --      directly or indirectly
294     }
295
296 data ForeignStubs = NoStubs
297                   | ForeignStubs
298                         SDoc            -- Header file prototypes for
299                                         --      "foreign exported" functions
300                         SDoc            -- C stubs to use when calling
301                                         --      "foreign exported" functions
302                         [FastString]    -- Headers that need to be included
303                                         --      into C code generated for this module
304                         [Id]            -- Foreign-exported binders
305                                         --      we have to generate code to register these
306
307
308 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl],  -- Sorted
309                                dcl_rules :: [RenamedRuleDecl],  -- Sorted
310                                dcl_insts :: [RenamedInstDecl] } -- Unsorted
311
312 mkIfaceDecls :: [RenamedTyClDecl] -> [RenamedRuleDecl] -> [RenamedInstDecl] -> IfaceDecls
313 -- Sort to put them in canonical order for version comparison
314 mkIfaceDecls tycls rules insts
315   = IfaceDecls { dcl_tycl  = sortLt lt_tycl tycls,
316                  dcl_rules = sortLt lt_rule rules,
317                  dcl_insts = sortLt lt_inst insts }
318   where
319     d1 `lt_tycl` d2 = tyClDeclName      d1 < tyClDeclName      d2
320     r1 `lt_rule` r2 = ifaceRuleDeclName r1 < ifaceRuleDeclName r2
321     i1 `lt_inst` i2 = instDeclDFun      i1 < instDeclDFun      i2
322 \end{code}
323
324 \begin{code}
325 emptyModIface :: Module -> ModIface
326 emptyModIface mod
327   = ModIface { mi_module   = mod,
328                mi_package  = basePackage, -- XXX fully bogus
329                mi_version  = initialVersionInfo,
330                mi_usages   = [],
331                mi_deps     = ([], []),
332                mi_orphan   = False,
333                mi_boot     = False,
334                mi_exports  = [],
335                mi_fixities = emptyNameEnv,
336                mi_globals  = Nothing,
337                mi_deprecs  = NoDeprecs,
338                mi_decls    = panic "emptyModIface: decls"
339     }           
340 \end{code}
341
342
343 %************************************************************************
344 %*                                                                      *
345                 Parsed interface files
346 %*                                                                      *
347 %************************************************************************
348
349 A ParsedIface is exactly as read from an interface file.
350
351 \begin{code}
352 type IfaceDeprecs = Maybe (Either DeprecTxt [(RdrName,DeprecTxt)])
353         -- Nothing        => NoDeprecs
354         -- Just (Left t)  => DeprecAll
355         -- Just (Right p) => DeprecSome
356
357 data ParsedIface
358   = ParsedIface {
359       pi_mod       :: ModuleName,
360       pi_pkg       :: PackageName,
361       pi_vers      :: Version,                          -- Module version number
362       pi_orphan    :: WhetherHasOrphans,                -- Whether this module has orphans
363       pi_deps      :: Dependencies,                     -- What it depends on
364       pi_usages    :: [Usage OccName],                  -- Usages
365       pi_exports   :: (Version, [RdrExportItem]),       -- Exports
366       pi_decls     :: [(Version, TyClDecl RdrName)],    -- Local definitions
367       pi_fixity    :: [FixitySig RdrName],              -- Local fixity declarations,
368       pi_insts     :: [InstDecl RdrName],               -- Local instance declarations
369       pi_rules     :: (Version, [RuleDecl RdrName]),    -- Rules, with their version
370       pi_deprecs   :: IfaceDeprecs                      -- Deprecations
371     }
372 \end{code}
373
374
375 %************************************************************************
376 %*                                                                      *
377 \subsection{The interactive context}
378 %*                                                                      *
379 %************************************************************************
380
381 \begin{code}
382 data InteractiveContext 
383   = InteractiveContext { 
384         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
385                                         -- these modules
386
387         ic_exports :: [Module],         -- Include just the exports of these
388                                         -- modules
389
390         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
391                                         -- ic_toplev_scope and ic_exports
392
393         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
394                                         -- during interaction
395
396         ic_type_env :: TypeEnv          -- Ditto for types
397     }
398
399 emptyInteractiveContext
400   = InteractiveContext { ic_toplev_scope = [],
401                          ic_exports = [],
402                          ic_rn_gbl_env = emptyRdrEnv,
403                          ic_rn_local_env = emptyRdrEnv,
404                          ic_type_env = emptyTypeEnv }
405
406 icPrintUnqual :: InteractiveContext -> PrintUnqualified
407 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
408 \end{code}
409
410
411 %************************************************************************
412 %*                                                                      *
413 \subsection{Type environment stuff}
414 %*                                                                      *
415 %************************************************************************
416
417 \begin{code}
418 typeEnvElts    :: TypeEnv -> [TyThing]
419 typeEnvClasses :: TypeEnv -> [Class]
420 typeEnvTyCons  :: TypeEnv -> [TyCon]
421 typeEnvIds     :: TypeEnv -> [Id]
422
423 typeEnvElts    env = nameEnvElts env
424 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
425 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
426 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
427
428 implicitTyThingIds :: [TyThing] -> [Id]
429 -- Add the implicit data cons and selectors etc 
430 implicitTyThingIds things
431   = concat (map go things)
432   where
433     go (AnId f)    = []
434     go (AClass cl) = classSelIds cl
435     go (ATyCon tc) = tyConGenIds tc ++
436                      tyConSelIds tc ++
437                      [ n | dc <- tyConDataCons_maybe tc `orElse` [],
438                            n  <- implicitConIds tc dc]
439                 -- Synonyms return empty list of constructors and selectors
440
441     implicitConIds tc dc        -- Newtypes have a constructor wrapper,
442                                 -- but no worker
443         | isNewTyCon tc = [dataConWrapId dc]
444         | otherwise     = [dataConWorkId dc, dataConWrapId dc]
445 \end{code}
446
447
448 \begin{code}
449 type TypeEnv = NameEnv TyThing
450
451 emptyTypeEnv = emptyNameEnv
452
453 mkTypeEnv :: [TyThing] -> TypeEnv
454 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
455                 
456 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
457 extendTypeEnvList env things
458   = extendNameEnvList env [(getName thing, thing) | thing <- things]
459
460 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
461 extendTypeEnvWithIds env ids
462   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
463 \end{code}
464
465 \begin{code}
466 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
467 lookupType hpt pte name
468   = case lookupModuleEnv hpt (nameModule name) of
469         Just details -> lookupNameEnv (md_types (hm_details details)) name
470         Nothing      -> lookupNameEnv pte name
471 \end{code}
472
473 %************************************************************************
474 %*                                                                      *
475 \subsection{Auxiliary types}
476 %*                                                                      *
477 %************************************************************************
478
479 These types are defined here because they are mentioned in ModDetails,
480 but they are mostly elaborated elsewhere
481
482 \begin{code}
483 data VersionInfo 
484   = VersionInfo {
485         vers_module  :: Version,        -- Changes when anything changes
486         vers_exports :: Version,        -- Changes when export list changes
487         vers_rules   :: Version,        -- Changes when any rule changes
488         vers_decls   :: NameEnv Version
489                 -- Versions for "big" names only (not data constructors, class ops)
490                 -- The version of an Id changes if its fixity changes
491                 -- Ditto data constructors, class operations, except that the version of
492                 -- the parent class/tycon changes
493                 --
494                 -- If a name isn't in the map, it means 'initialVersion'
495     }
496
497 initialVersionInfo :: VersionInfo
498 initialVersionInfo = VersionInfo { vers_module  = initialVersion,
499                                    vers_exports = initialVersion,
500                                    vers_rules   = initialVersion,
501                                    vers_decls   = emptyNameEnv
502                         }
503
504 lookupVersion :: NameEnv Version -> Name -> Version
505 lookupVersion env name = lookupNameEnv env name `orElse` initialVersion
506
507 data Deprecations = NoDeprecs
508                   | DeprecAll DeprecTxt                         -- Whole module deprecated
509                   | DeprecSome (NameEnv (Name,DeprecTxt))       -- Some things deprecated
510                                                                 -- Just "big" names
511                 -- We keep the Name in the range, so we can print them out
512
513 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
514 lookupDeprec NoDeprecs        name = Nothing
515 lookupDeprec (DeprecAll  txt) name = Just txt
516 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
517                                             Just (_, txt) -> Just txt
518                                             Nothing       -> Nothing
519
520 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
521 plusDeprecs d NoDeprecs = d
522 plusDeprecs NoDeprecs d = d
523 plusDeprecs d (DeprecAll t) = DeprecAll t
524 plusDeprecs (DeprecAll t) d = DeprecAll t
525 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
526
527 instance Eq Deprecations where
528   -- Used when checking whether we need write a new interface
529   NoDeprecs       == NoDeprecs       = True
530   (DeprecAll t1)  == (DeprecAll t2)  = t1 == t2
531   (DeprecSome e1) == (DeprecSome e2) = nameEnvElts e1 == nameEnvElts e2
532   d1              == d2              = False
533 \end{code}
534
535
536 \begin{code}
537 type Avails       = [AvailInfo]
538 type AvailInfo    = GenAvailInfo Name
539 type RdrAvailInfo = GenAvailInfo OccName
540
541 data GenAvailInfo name  = Avail name     -- An ordinary identifier
542                         | AvailTC name   -- The name of the type or class
543                                   [name] -- The available pieces of type/class.
544                                          -- NB: If the type or class is itself
545                                          -- to be in scope, it must be in this list.
546                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
547                         deriving( Eq )
548                         -- Equality used when deciding if the interface has changed
549
550 type RdrExportItem = (ModuleName, [RdrAvailInfo])
551 type ExportItem    = (ModuleName, [AvailInfo])
552
553 availsToNameSet :: [AvailInfo] -> NameSet
554 availsToNameSet avails = foldl add emptyNameSet avails
555                        where
556                          add set avail = addListToNameSet set (availNames avail)
557
558 availName :: GenAvailInfo name -> name
559 availName (Avail n)     = n
560 availName (AvailTC n _) = n
561
562 availNames :: GenAvailInfo name -> [name]
563 availNames (Avail n)      = [n]
564 availNames (AvailTC n ns) = ns
565
566 instance Outputable n => Outputable (GenAvailInfo n) where
567    ppr = pprAvail
568
569 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
570 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
571                                         []  -> empty
572                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
573
574 pprAvail (Avail n) = ppr n
575 \end{code}
576
577 \begin{code}
578 type FixityEnv = NameEnv (FixitySig Name)
579         -- We keep the whole fixity sig so that we
580         -- can report line-number info when there is a duplicate
581         -- fixity declaration
582
583 emptyFixityEnv :: FixityEnv
584 emptyFixityEnv = emptyNameEnv
585
586 lookupFixity :: FixityEnv -> Name -> Fixity
587 lookupFixity env n = case lookupNameEnv env n of
588                         Just (FixitySig _ fix _) -> fix
589                         Nothing                  -> defaultFixity
590
591 collectFixities :: FixityEnv -> [TyClDecl Name] -> [FixitySig Name]
592 -- Collect fixities for the specified declarations
593 collectFixities env decls
594   = [ fix
595     | d <- decls, (n,_) <- tyClDeclNames d,
596       Just fix <- [lookupNameEnv env n]
597     ]
598 \end{code}
599
600
601 %************************************************************************
602 %*                                                                      *
603 \subsection{WhatsImported}
604 %*                                                                      *
605 %************************************************************************
606
607 \begin{code}
608 type WhetherHasOrphans   = Bool
609         -- An "orphan" is 
610         --      * an instance decl in a module other than the defn module for 
611         --              one of the tycons or classes in the instance head
612         --      * a transformation rule in a module other than the one defining
613         --              the function in the head of the rule.
614
615 type IsBootInterface = Bool
616
617 -- Dependency info about modules and packages below this one
618 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
619 --
620 -- Invariant: the dependencies of a module M never includes M
621 type Dependencies
622   = ([(ModuleName, WhetherHasOrphans, IsBootInterface)], [PackageName])
623
624 data Usage name 
625   = Usage { usg_name     :: ModuleName,         -- Name of the module
626             usg_mod      :: Version,            -- Module version
627             usg_exports  :: Maybe Version,      -- Export-list version, if we depend on it
628             usg_entities :: [(name,Version)],   -- Sorted by occurrence name
629             usg_rules    :: Version             -- Rules version
630     }       deriving( Eq )
631         -- This type doesn't let you say "I imported f but none of the rules in
632         -- the module". If you use anything in the module you get its rule version
633         -- So if the rules change, you'll recompile, even if you don't use them.
634         -- This is easy to implement, and it's safer: you might not have used the rules last
635         -- time round, but if someone has added a new rule you might need it this time
636
637         -- The export list field is (Just v) if we depend on the export list:
638         --      i.e. we imported the module without saying exactly what we imported
639         -- We need to recompile if the module exports changes, because we might
640         -- now have a name clash in the importing module.
641 \end{code}
642
643
644 %************************************************************************
645 %*                                                                      *
646 \subsection{The persistent compiler state}
647 %*                                                                      *
648 %************************************************************************
649
650 The @PersistentCompilerState@ persists across successive calls to the
651 compiler.
652
653 \begin{code}
654 data PersistentCompilerState 
655    = PCS {
656         pcs_nc  :: !NameCache,
657         pcs_EPS :: !ExternalPackageState
658      }
659 \end{code}
660
661
662 \begin{code}
663 type PackageTypeEnv  = TypeEnv
664 type PackageRuleBase = RuleBase
665 type PackageInstEnv  = InstEnv
666
667 data ExternalPackageState
668   = EPS {
669         eps_PIT :: !PackageIfaceTable,
670                 -- The ModuleIFaces for modules in external packages
671                 -- whose interfaces we have opened
672                 -- The declarations in these interface files are held in
673                 -- eps_decls, eps_insts, eps_rules (below), not in the 
674                 -- mi_decls fields of the iPIT.  
675                 -- What _is_ in the iPIT is:
676                 --      * The Module 
677                 --      * Version info
678                 --      * Its exports
679                 --      * Fixities
680                 --      * Deprecations
681
682         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
683
684         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
685                                                 --   all the external-package modules
686         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
687
688
689         -- Holding pens for stuff that has been read in from file,
690         -- but not yet slurped into the renamer
691         eps_decls      :: !DeclsMap,
692                 -- A single, global map of Names to unslurped decls
693         eps_insts      :: !IfaceInsts,
694                 -- The as-yet un-slurped instance decls; this bag is depleted when we
695                 -- slurp an instance decl so that we don't slurp the same one twice.
696                 -- Each is 'gated' by the names that must be available before
697                 -- this instance decl is needed.
698         eps_rules      :: !IfaceRules,
699                 -- Similar to instance decls, only for rules
700
701         eps_inst_gates :: !NameSet      -- Gates for instance decls
702                 -- The instance gates must accumulate across
703                 -- all invocations of the renamer; 
704                 -- see "the gating story" in RnIfaces.lhs
705                 -- These names should all be from other packages;
706                 -- for the home package we have all the instance
707                 -- declarations anyhow
708   }
709 \end{code}
710
711 The NameCache makes sure that there is just one Unique assigned for
712 each original name; i.e. (module-name, occ-name) pair.  The Name is
713 always stored as a Global, and has the SrcLoc of its binding location.
714 Actually that's not quite right.  When we first encounter the original
715 name, we might not be at its binding site (e.g. we are reading an
716 interface file); so we give it 'noSrcLoc' then.  Later, when we find
717 its binding site, we fix it up.
718
719 Exactly the same is true of the Module stored in the Name.  When we first
720 encounter the occurrence, we may not know the details of the module, so
721 we just store junk.  Then when we find the binding site, we fix it up.
722
723 \begin{code}
724 data NameCache
725  = NameCache {  nsUniqs :: UniqSupply,
726                 -- Supply of uniques
727                 nsNames :: OrigNameCache,
728                 -- Ensures that one original name gets one unique
729                 nsIPs   :: OrigIParamCache
730                 -- Ensures that one implicit parameter name gets one unique
731    }
732
733 type OrigNameCache = ModuleEnv (Module, OccNameCache)
734         -- Maps a module *name* to a Module, 
735         -- plus the OccNameEnv fot that module
736 type OccNameCache = FiniteMap OccName Name
737         -- Maps the OccName to a Name
738         -- A FiniteMap because OccNames have a Namespace/Faststring pair
739
740 type OrigIParamCache = FiniteMap (IPName RdrName) (IPName Name)
741 \end{code}
742
743 A DeclsMap contains a binding for each Name in the declaration
744 including the constructors of a type decl etc.  The Bool is True just
745 for the 'main' Name.
746
747 \begin{code}
748 type DeclsMap = (NameEnv (AvailInfo, Bool, (Module, TyClDecl RdrName)), Int)
749                                                 -- The Int says how many have been sucked in
750
751 type IfaceInsts = GatedDecls (InstDecl RdrName)
752 type IfaceRules = GatedDecls (RuleDecl RdrName)
753
754 type GatedDecls d = (Bag (GatedDecl d), Int)    -- The Int says how many have been sucked in
755 type GatedDecl  d = (GateFn, (Module, d))
756 type GateFn       = (Name -> Bool) -> Bool      -- Returns True <=> gate is open
757                                                 -- The (Name -> Bool) fn returns True for visible Names
758         -- For example, suppose this is in an interface file
759         --      instance C T where ...
760         -- We want to slurp this decl if both C and T are "visible" in 
761         -- the importing module.  See "The gating story" in RnIfaces for details.
762 \end{code}
763
764
765 %************************************************************************
766 %*                                                                      *
767 \subsection{Linkable stuff}
768 %*                                                                      *
769 %************************************************************************
770
771 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
772 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
773
774 \begin{code}
775 data Linkable = LM {
776   linkableTime     :: ClockTime,        -- Time at which this linkable was built
777                                         -- (i.e. when the bytecodes were produced,
778                                         --       or the mod date on the files)
779   linkableModName  :: ModuleName,       -- Should be Module, but see below
780   linkableUnlinked :: [Unlinked]
781  }
782
783 isObjectLinkable :: Linkable -> Bool
784 isObjectLinkable l = all isObject (linkableUnlinked l)
785
786 instance Outputable Linkable where
787    ppr (LM when_made mod unlinkeds)
788       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
789         $$ nest 3 (ppr unlinkeds)
790
791 -------------------------------------------
792 data Unlinked
793    = DotO FilePath
794    | DotA FilePath
795    | DotDLL FilePath
796    | BCOs CompiledByteCode
797
798 #ifndef GHCI
799 data CompiledByteCode = NoByteCode
800 #endif
801
802 instance Outputable Unlinked where
803    ppr (DotO path)   = text "DotO" <+> text path
804    ppr (DotA path)   = text "DotA" <+> text path
805    ppr (DotDLL path) = text "DotDLL" <+> text path
806 #ifdef GHCI
807    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
808 #else
809    ppr (BCOs bcos)   = text "No byte code"
810 #endif
811
812 isObject (DotO _)   = True
813 isObject (DotA _)   = True
814 isObject (DotDLL _) = True
815 isObject _          = False
816
817 isInterpretable = not . isObject
818
819 nameOfObject (DotO fn)   = fn
820 nameOfObject (DotA fn)   = fn
821 nameOfObject (DotDLL fn) = fn
822
823 byteCodeOfObject (BCOs bc) = bc
824 \end{code}
825
826
827 %************************************************************************
828 %*                                                                      *
829 \subsection{Provenance and export info}
830 %*                                                                      *
831 %************************************************************************
832
833 A LocalRdrEnv is used for local bindings (let, where, lambda, case)
834 Also used in 
835
836 \begin{code}
837 type LocalRdrEnv = RdrNameEnv Name
838
839 extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv
840 extendLocalRdrEnv env names
841   = addListToRdrEnv env [(mkRdrUnqual (nameOccName n), n) | n <- names]
842 \end{code}
843
844 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
845 one for each module, corresponding to that module's top-level scope.
846
847 \begin{code}
848 type GlobalRdrEnv = RdrNameEnv [GlobalRdrElt]
849         -- The list is because there may be name clashes
850         -- These only get reported on lookup, not on construction
851
852 emptyGlobalRdrEnv = emptyRdrEnv
853
854 data GlobalRdrElt 
855   = GRE { gre_name   :: Name,
856           gre_parent :: Name,   -- Name of the "parent" structure
857                                 --      * the tycon of a data con
858                                 --      * the class of a class op
859                                 -- For others it's just the same as gre_name
860           gre_prov   :: Provenance,             -- Why it's in scope
861           gre_deprec :: Maybe DeprecTxt         -- Whether this name is deprecated
862     }
863
864 instance Outputable GlobalRdrElt where
865   ppr gre = ppr (gre_name gre) <+> 
866             parens (hsep [text "parent:" <+> ppr (gre_parent gre) <> comma,
867                           pprNameProvenance gre])
868 pprGlobalRdrEnv env
869   = vcat (map pp (rdrEnvToList env))
870   where
871     pp (rn, gres) = ppr rn <> colon <+> 
872                     vcat [ ppr (gre_name gre) <+> pprNameProvenance gre
873                          | gre <- gres]
874
875 isLocalGRE :: GlobalRdrElt -> Bool
876 isLocalGRE (GRE {gre_prov = LocalDef}) = True
877 isLocalGRE other                       = False
878 \end{code}
879
880 @unQualInScope@ returns a function that takes a @Name@ and tells whether
881 its unqualified name is in scope.  This is put as a boolean flag in
882 the @Name@'s provenance to guide whether or not to print the name qualified
883 in error messages.
884
885 \begin{code}
886 unQualInScope :: GlobalRdrEnv -> Name -> Bool
887 -- True if 'f' is in scope, and has only one binding,
888 -- and the thing it is bound to is the name we are looking for
889 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
890 --
891 -- Also checks for built-in syntax, which is always 'in scope'
892 --
893 -- This fn is only efficient if the shared 
894 -- partial application is used a lot.
895 unQualInScope env
896   = \n -> n `elemNameSet` unqual_names || isBuiltInSyntaxName n
897   where
898     unqual_names :: NameSet
899     unqual_names = foldRdrEnv add emptyNameSet env
900     add rdr_name [gre] unquals | isUnqual rdr_name = addOneToNameSet unquals (gre_name gre)
901     add _        _     unquals                     = unquals
902 \end{code}
903
904 The "provenance" of something says how it came to be in scope.
905
906 \begin{code}
907 data Provenance
908   = LocalDef                    -- Defined locally
909
910   | NonLocalDef                 -- Defined non-locally
911         ImportReason
912
913 -- Just used for grouping error messages (in RnEnv.warnUnusedBinds)
914 instance Eq Provenance where
915   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
916
917 instance Eq ImportReason where
918   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
919
920 instance Ord Provenance where
921    compare LocalDef LocalDef = EQ
922    compare LocalDef (NonLocalDef _) = LT
923    compare (NonLocalDef _) LocalDef = GT
924
925    compare (NonLocalDef reason1) (NonLocalDef reason2) 
926       = compare reason1 reason2
927
928 instance Ord ImportReason where
929    compare ImplicitImport ImplicitImport = EQ
930    compare ImplicitImport (UserImport _ _ _) = LT
931    compare (UserImport _ _ _) ImplicitImport = GT
932    compare (UserImport m1 loc1 _) (UserImport m2 loc2 _) 
933       = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
934
935
936 data ImportReason
937   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
938                                         -- Note the M may well not be the defining module
939                                         -- for this thing!
940         -- The Bool is true iff the thing was named *explicitly* in the import spec,
941         -- rather than being imported as part of a group; e.g.
942         --      import B
943         --      import C( T(..) )
944         -- Here, everything imported by B, and the constructors of T
945         -- are not named explicitly; only T is named explicitly.
946         -- This info is used when warning of unused names.
947
948   | ImplicitImport                      -- Imported implicitly for some other reason
949 \end{code}
950
951 \begin{code}
952 hasBetterProv :: Provenance -> Provenance -> Bool
953 -- Choose 
954 --      a local thing                 over an   imported thing
955 --      a user-imported thing         over a    non-user-imported thing
956 --      an explicitly-imported thing  over an   implicitly imported thing
957 hasBetterProv LocalDef                            _                            = True
958 hasBetterProv (NonLocalDef (UserImport _ _ _   )) (NonLocalDef ImplicitImport) = True
959 hasBetterProv _                                   _                            = False
960
961 pprNameProvenance :: GlobalRdrElt -> SDoc
962 pprNameProvenance (GRE {gre_name = name, gre_prov = prov})
963   = case prov of
964         LocalDef        -> ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
965         NonLocalDef why ->  sep [ppr_reason why, 
966                                  nest 2 (ppr_defn (nameSrcLoc name))]
967
968 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
969 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
970
971 ppr_defn loc | isGoodSrcLoc loc = parens (ptext SLIT("at") <+> ppr loc)
972              | otherwise        = empty
973 \end{code}