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