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