[project @ 2000-10-31 08:08:38 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         ModuleLocation(..),
9
10         ModDetails(..), ModIface(..), 
11         HomeSymbolTable, PackageTypeEnv,
12         HomeIfaceTable, PackageIfaceTable, emptyIfaceTable,
13         lookupIface, lookupIfaceByModName,
14         emptyModIface,
15
16         IfaceDecls(..), 
17
18         VersionInfo(..), initialVersionInfo,
19
20         TyThing(..), isTyClThing,
21
22         TypeEnv, lookupType, mkTypeEnv, extendTypeEnvList, 
23         typeEnvClasses, typeEnvTyCons,
24
25         WhetherHasOrphans, ImportVersion, WhatsImported(..),
26         PersistentRenamerState(..), IsBootInterface, Avails, DeclsMap,
27         IfaceInsts, IfaceRules, GatedDecl,
28         OrigNameEnv(..), OrigNameNameEnv, OrigNameIParamEnv,
29         AvailEnv, AvailInfo, GenAvailInfo(..),
30         PersistentCompilerState(..),
31
32         Deprecations(..), lookupDeprec,
33
34         InstEnv, ClsInstEnv, DFunId,
35         PackageInstEnv, PackageRuleBase,
36
37         GlobalRdrEnv, RdrAvailInfo,
38
39         -- Provenance
40         Provenance(..), ImportReason(..), PrintUnqualified,
41         pprNameProvenance, hasBetterProv
42
43     ) where
44
45 #include "HsVersions.h"
46
47 import RdrName          ( RdrNameEnv, emptyRdrEnv )
48 import Name             ( Name, NameEnv, NamedThing,
49                           emptyNameEnv, extendNameEnv, 
50                           lookupNameEnv, emptyNameEnv, nameEnvElts,
51                           isLocallyDefined, getName, nameModule,
52                           nameSrcLoc )
53 import NameSet          ( NameSet )
54 import OccName          ( OccName )
55 import Module           ( Module, ModuleName, ModuleEnv,
56                           lookupModuleEnv, lookupModuleEnvByName
57                         )
58 import Rules            ( RuleBase )
59 import VarSet           ( TyVarSet )
60 import Id               ( Id )
61 import Class            ( Class )
62 import TyCon            ( TyCon )
63
64 import BasicTypes       ( Version, initialVersion, Fixity )
65
66 import HsSyn            ( DeprecTxt )
67 import RdrHsSyn         ( RdrNameHsDecl, RdrNameTyClDecl )
68 import RnHsSyn          ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
69
70 import CoreSyn          ( IdCoreRule )
71 import Type             ( Type )
72
73 import FiniteMap        ( FiniteMap )
74 import Bag              ( Bag )
75 import Maybes           ( seqMaybe )
76 import UniqFM           ( UniqFM, emptyUFM )
77 import Outputable
78 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
79 import Util             ( thenCmp )
80 import UniqSupply       ( UniqSupply )
81 \end{code}
82
83 %************************************************************************
84 %*                                                                      *
85 \subsection{Module locations}
86 %*                                                                      *
87 %************************************************************************
88
89 \begin{code}
90 data ModuleLocation
91    = ModuleLocation {
92         ml_hs_file   :: Maybe FilePath,
93         ml_hspp_file :: Maybe FilePath,  -- path of preprocessed source
94         ml_hi_file   :: Maybe FilePath,
95         ml_obj_file  :: Maybe FilePath
96      }
97      deriving Show
98
99 instance Outputable ModuleLocation where
100    ppr = text . show
101 \end{code}
102
103 For a module in another package, the hs_file and obj_file
104 components of ModuleLocation are undefined.  
105
106 The locations specified by a ModuleLocation may or may not
107 correspond to actual files yet: for example, even if the object
108 file doesn't exist, the ModuleLocation still contains the path to
109 where the object file will reside if/when it is created.
110
111
112 %************************************************************************
113 %*                                                                      *
114 \subsection{Symbol tables and Module details}
115 %*                                                                      *
116 %************************************************************************
117
118 A @ModIface@ plus a @ModDetails@ summarises everything we know 
119 about a compiled module.  The @ModIface@ is the stuff *before* linking,
120 and can be written out to an interface file.  The @ModDetails@ is after
121 linking; it is the "linked" form of the mi_decls field.
122
123 \begin{code}
124 data ModIface 
125    = ModIface {
126         mi_module   :: Module,                  -- Complete with package info
127         mi_version  :: VersionInfo,             -- Module version number
128         mi_orphan   :: WhetherHasOrphans,       -- Whether this module has orphans
129         mi_boot     :: IsBootInterface,         -- Whether this interface was read from an hi-boot file
130
131         mi_usages   :: [ImportVersion Name],    -- Usages; kept sorted so that it's easy
132                                                 -- to decide whether to write a new iface file
133                                                 -- (changing usages doesn't affect the version of
134                                                 --  this module)
135
136         mi_exports  :: [(ModuleName,Avails)],   -- What it exports
137                                                 -- Kept sorted by (mod,occ),
138                                                 -- to make version comparisons easier
139
140         mi_globals  :: GlobalRdrEnv,            -- Its top level environment
141
142         mi_fixities :: NameEnv Fixity,          -- Fixities
143         mi_deprecs  :: Deprecations,            -- Deprecations
144
145         mi_decls    :: IfaceDecls               -- The RnDecls form of ModDetails
146      }
147
148 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl],  -- Sorted
149                                dcl_rules :: [RenamedRuleDecl],  -- Sorted
150                                dcl_insts :: [RenamedInstDecl] } -- Unsorted
151
152 -- typechecker should only look at this, not ModIface
153 -- Should be able to construct ModDetails from mi_decls in ModIface
154 data ModDetails
155    = ModDetails {
156         -- The next three fields are created by the typechecker
157         md_types    :: TypeEnv,
158         md_insts    :: [DFunId],        -- Dfun-ids for the instances in this module
159         md_rules    :: [IdCoreRule]     -- Domain may include Ids from other modules
160      }
161 \end{code}
162
163 \begin{code}
164 emptyModDetails :: ModDetails
165 emptyModDetails
166   = ModDetails { md_types = emptyTypeEnv,
167                  md_insts = [],
168                  md_rules = []
169     }
170
171 emptyModIface :: Module -> ModIface
172 emptyModIface mod
173   = ModIface { mi_module   = mod,
174                mi_version  = initialVersionInfo,
175                mi_usages   = [],
176                mi_orphan   = False,
177                mi_boot     = False,
178                mi_exports  = [],
179                mi_fixities = emptyNameEnv,
180                mi_globals  = emptyRdrEnv,
181                mi_deprecs  = NoDeprecs,
182                mi_decls    = panic "emptyModIface: decls"
183     }           
184 \end{code}
185
186 Symbol tables map modules to ModDetails:
187
188 \begin{code}
189 type SymbolTable        = ModuleEnv ModDetails
190 type IfaceTable         = ModuleEnv ModIface
191
192 type HomeIfaceTable     = IfaceTable
193 type PackageIfaceTable  = IfaceTable
194
195 type HomeSymbolTable    = SymbolTable   -- Domain = modules in the home package
196
197 emptyIfaceTable :: IfaceTable
198 emptyIfaceTable = emptyUFM
199 \end{code}
200
201 Simple lookups in the symbol table.
202
203 \begin{code}
204 lookupIface :: HomeIfaceTable -> PackageIfaceTable
205             -> Module -> Name           -- The module is to use for locally-defined names
206             -> Maybe ModIface
207 -- We often have two IfaceTables, and want to do a lookup
208 lookupIface hit pit this_mod name
209   | isLocallyDefined name = lookupModuleEnv hit this_mod
210   | otherwise             = lookupModuleEnv hit mod `seqMaybe` lookupModuleEnv pit mod
211   where
212     mod = nameModule name
213
214 lookupIfaceByModName :: ModuleEnv a -> ModuleEnv a -> ModuleName -> Maybe a
215 -- We often have two Symbol- or IfaceTables, and want to do a lookup
216 lookupIfaceByModName ht pt mod
217   = lookupModuleEnvByName ht mod `seqMaybe` lookupModuleEnvByName pt mod
218 \end{code}
219
220
221 %************************************************************************
222 %*                                                                      *
223 \subsection{Type environment stuff}
224 %*                                                                      *
225 %************************************************************************
226
227 \begin{code}
228 data TyThing = AnId   Id
229              | ATyCon TyCon
230              | AClass Class
231
232 isTyClThing :: TyThing -> Bool
233 isTyClThing (ATyCon _) = True
234 isTyClThing (AClass _) = True
235 isTyClThing (AnId   _) = False
236
237 instance NamedThing TyThing where
238   getName (AnId id)   = getName id
239   getName (ATyCon tc) = getName tc
240   getName (AClass cl) = getName cl
241
242 typeEnvClasses env = [cl | AClass cl <- nameEnvElts env]
243 typeEnvTyCons  env = [tc | ATyCon tc <- nameEnvElts env] 
244
245 \end{code}
246
247
248 \begin{code}
249 type TypeEnv = NameEnv TyThing
250
251 emptyTypeEnv = emptyNameEnv
252
253 mkTypeEnv :: [TyThing] -> TypeEnv
254 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
255                 
256 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
257 extendTypeEnvList env things
258   = foldl add_thing env things
259   where
260     add_thing :: TypeEnv -> TyThing -> TypeEnv
261     add_thing env thing = extendNameEnv env (getName thing) thing
262 \end{code}
263
264 \begin{code}
265 lookupType :: HomeSymbolTable -> PackageTypeEnv -> Name -> Maybe TyThing
266 lookupType hst pte name
267   = ASSERT2( not (isLocallyDefined name), ppr name )
268     case lookupModuleEnv hst (nameModule name) of
269         Just details -> lookupNameEnv (md_types details) name
270         Nothing      -> lookupNameEnv pte name
271 \end{code}
272
273 %************************************************************************
274 %*                                                                      *
275 \subsection{Auxiliary types}
276 %*                                                                      *
277 %************************************************************************
278
279 These types are defined here because they are mentioned in ModDetails,
280 but they are mostly elaborated elsewhere
281
282 \begin{code}
283 data VersionInfo 
284   = VersionInfo {
285         vers_module  :: Version,        -- Changes when anything changes
286         vers_exports :: Version,        -- Changes when export list changes
287         vers_rules   :: Version,        -- Changes when any rule changes
288         vers_decls   :: NameEnv Version
289                 -- Versions for "big" names only (not data constructors, class ops)
290                 -- The version of an Id changes if its fixity changes
291                 -- Ditto data constructors, class operations, except that the version of
292                 -- the parent class/tycon changes
293     }
294
295 initialVersionInfo :: VersionInfo
296 initialVersionInfo = VersionInfo { vers_module  = initialVersion,
297                                    vers_exports = initialVersion,
298                                    vers_rules   = initialVersion,
299                                    vers_decls   = emptyNameEnv }
300
301 data Deprecations = NoDeprecs
302                   | DeprecAll DeprecTxt                         -- Whole module deprecated
303                   | DeprecSome (NameEnv (Name,DeprecTxt))       -- Some things deprecated
304                                                                 -- Just "big" names
305                 -- We keep the Name in the range, so we can print them out
306
307 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
308 lookupDeprec NoDeprecs        name = Nothing
309 lookupDeprec (DeprecAll  txt) name = Just txt
310 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
311                                             Just (_, txt) -> Just txt
312                                             Nothing       -> Nothing
313
314 type InstEnv    = UniqFM ClsInstEnv             -- Maps Class to instances for that class
315
316 type ClsInstEnv = [(TyVarSet, [Type], DFunId)]  -- The instances for a particular class
317 type DFunId     = Id
318 \end{code}
319
320
321 \begin{code}
322 type Avails       = [AvailInfo]
323 type AvailInfo    = GenAvailInfo Name
324 type RdrAvailInfo = GenAvailInfo OccName
325
326 data GenAvailInfo name  = Avail name     -- An ordinary identifier
327                         | AvailTC name   -- The name of the type or class
328                                   [name] -- The available pieces of type/class.
329                                          -- NB: If the type or class is itself
330                                          -- to be in scope, it must be in this list.
331                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
332                         deriving( Eq )
333                         -- Equality used when deciding if the interface has changed
334
335 type AvailEnv     = NameEnv AvailInfo   -- Maps a Name to the AvailInfo that contains it
336 \end{code}
337
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection{ModIface}
342 %*                                                                      *
343 %************************************************************************
344
345 \begin{code}
346 type WhetherHasOrphans   = Bool
347         -- An "orphan" is 
348         --      * an instance decl in a module other than the defn module for 
349         --              one of the tycons or classes in the instance head
350         --      * a transformation rule in a module other than the one defining
351         --              the function in the head of the rule.
352
353 type IsBootInterface     = Bool
354
355 type ImportVersion name  = (ModuleName, WhetherHasOrphans, IsBootInterface, WhatsImported name)
356
357 data WhatsImported name  = NothingAtAll                         -- The module is below us in the
358                                                                 -- hierarchy, but we import nothing
359
360                          | Everything Version           -- Used for modules from other packages;
361                                                         -- we record only the module's version number
362
363                          | Specifically 
364                                 Version                 -- Module version
365                                 (Maybe Version)         -- Export-list version, if we depend on it
366                                 [(name,Version)]        -- List guaranteed non-empty
367                                 Version                 -- Rules version
368
369                          deriving( Eq )
370         -- 'Specifically' doesn't let you say "I imported f but none of the rules in
371         -- the module". If you use anything in the module you get its rule version
372         -- So if the rules change, you'll recompile, even if you don't use them.
373         -- This is easy to implement, and it's safer: you might not have used the rules last
374         -- time round, but if someone has added a new rule you might need it this time
375
376         -- The export list field is (Just v) if we depend on the export list:
377         --      we imported the module without saying exactly what we imported
378         -- We need to recompile if the module exports changes, because we might
379         -- now have a name clash in the importing module.
380 \end{code}
381
382
383 %************************************************************************
384 %*                                                                      *
385 \subsection{The persistent compiler state}
386 %*                                                                      *
387 %************************************************************************
388
389 \begin{code}
390 data PersistentCompilerState 
391    = PCS {
392         pcs_PIT :: PackageIfaceTable,   -- Domain = non-home-package modules
393                                         --   the mi_decls component is empty
394
395         pcs_PTE :: PackageTypeEnv,      -- Domain = non-home-package modules
396                                         --   except that the InstEnv components is empty
397
398         pcs_insts :: PackageInstEnv,    -- The total InstEnv accumulated from all
399                                         --   the non-home-package modules
400
401         pcs_rules :: PackageRuleBase,   -- Ditto RuleEnv
402
403         pcs_PRS :: PersistentRenamerState
404      }
405
406 \end{code}
407
408 The @PersistentRenamerState@ persists across successive calls to the
409 compiler.
410
411 It contains:
412   * A name supply, which deals with allocating unique names to
413     (Module,OccName) original names, 
414  
415   * An accumulated TypeEnv from all the modules in imported packages
416
417   * An accumulated InstEnv from all the modules in imported packages
418     The point is that we don't want to keep recreating it whenever
419     we compile a new module.  The InstEnv component of pcPST is empty.
420     (This means we might "see" instances that we shouldn't "really" see;
421     but the Haskell Report is vague on what is meant to be visible, 
422     so we just take the easy road here.)
423
424   * Ditto for rules
425
426   * A "holding pen" for declarations that have been read out of
427     interface files but not yet sucked in, renamed, and typechecked
428
429 \begin{code}
430 type PackageTypeEnv  = TypeEnv
431 type PackageRuleBase = RuleBase
432 type PackageInstEnv  = InstEnv
433
434 data PersistentRenamerState
435   = PRS { prsOrig  :: OrigNameEnv,
436           prsDecls :: DeclsMap,
437           prsInsts :: IfaceInsts,
438           prsRules :: IfaceRules,
439           prsNS    :: UniqSupply
440     }
441 \end{code}
442
443 The OrigNameEnv makes sure that there is just one Unique assigned for
444 each original name; i.e. (module-name, occ-name) pair.  The Name is
445 always stored as a Global, and has the SrcLoc of its binding location.
446 Actually that's not quite right.  When we first encounter the original
447 name, we might not be at its binding site (e.g. we are reading an
448 interface file); so we give it 'noSrcLoc' then.  Later, when we find
449 its binding site, we fix it up.
450
451 Exactly the same is true of the Module stored in the Name.  When we first
452 encounter the occurrence, we may not know the details of the module, so
453 we just store junk.  Then when we find the binding site, we fix it up.
454
455 \begin{code}
456 data OrigNameEnv
457  = Orig { origNames  :: OrigNameNameEnv,
458                 -- Ensures that one original name gets one unique
459           origIParam :: OrigNameIParamEnv
460                 -- Ensures that one implicit parameter name gets one unique
461    }
462
463 type OrigNameNameEnv   = FiniteMap (ModuleName,OccName) Name
464 type OrigNameIParamEnv = FiniteMap OccName Name
465 \end{code}
466
467
468 A DeclsMap contains a binding for each Name in the declaration
469 including the constructors of a type decl etc.  The Bool is True just
470 for the 'main' Name.
471
472 \begin{code}
473 type DeclsMap = NameEnv (AvailInfo, Bool, (Module, RdrNameTyClDecl))
474
475 type IfaceInsts = Bag GatedDecl
476 type IfaceRules = Bag GatedDecl
477
478 type GatedDecl = (NameSet, (Module, RdrNameHsDecl))
479 \end{code}
480
481
482 %************************************************************************
483 %*                                                                      *
484 \subsection{Provenance and export info}
485 %*                                                                      *
486 %************************************************************************
487
488 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
489 one for each module, corresponding to that module's top-level scope.
490
491 \begin{code}
492 type GlobalRdrEnv = RdrNameEnv [(Name,Provenance)]      -- The list is because there may be name clashes
493                                                         -- These only get reported on lookup,
494                                                         -- not on construction
495 \end{code}
496
497 The "provenance" of something says how it came to be in scope.
498
499 \begin{code}
500 data Provenance
501   = LocalDef                    -- Defined locally
502
503   | NonLocalDef                 -- Defined non-locally
504         ImportReason
505         PrintUnqualified
506
507 -- Just used for grouping error messages (in RnEnv.warnUnusedBinds)
508 instance Eq Provenance where
509   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
510
511 instance Eq ImportReason where
512   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
513
514 instance Ord Provenance where
515    compare LocalDef LocalDef = EQ
516    compare LocalDef (NonLocalDef _ _) = LT
517    compare (NonLocalDef _ _) LocalDef = GT
518
519    compare (NonLocalDef reason1 _) (NonLocalDef reason2 _) 
520       = compare reason1 reason2
521
522 instance Ord ImportReason where
523    compare ImplicitImport ImplicitImport = EQ
524    compare ImplicitImport (UserImport _ _ _) = LT
525    compare (UserImport _ _ _) ImplicitImport = GT
526    compare (UserImport m1 loc1 _) (UserImport m2 loc2 _) 
527       = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
528
529
530 data ImportReason
531   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
532                                         -- Note the M may well not be the defining module
533                                         -- for this thing!
534         -- The Bool is true iff the thing was named *explicitly* in the import spec,
535         -- rather than being imported as part of a group; e.g.
536         --      import B
537         --      import C( T(..) )
538         -- Here, everything imported by B, and the constructors of T
539         -- are not named explicitly; only T is named explicitly.
540         -- This info is used when warning of unused names.
541
542   | ImplicitImport                      -- Imported implicitly for some other reason
543                         
544
545 type PrintUnqualified = Bool    -- True <=> the unqualified name of this thing is
546                                 -- in scope in this module, so print it 
547                                 -- unqualified in error messages
548 \end{code}
549
550 \begin{code}
551 hasBetterProv :: Provenance -> Provenance -> Bool
552 -- Choose 
553 --      a local thing                 over an   imported thing
554 --      a user-imported thing         over a    non-user-imported thing
555 --      an explicitly-imported thing  over an   implicitly imported thing
556 hasBetterProv LocalDef                              _                              = True
557 hasBetterProv (NonLocalDef (UserImport _ _ True) _) _                              = True
558 hasBetterProv (NonLocalDef (UserImport _ _ _   ) _) (NonLocalDef ImplicitImport _) = True
559 hasBetterProv _                                     _                              = False
560
561 pprNameProvenance :: Name -> Provenance -> SDoc
562 pprNameProvenance name LocalDef            = ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
563 pprNameProvenance name (NonLocalDef why _) = sep [ppr_reason why, 
564                                               nest 2 (parens (ppr_defn (nameSrcLoc name)))]
565
566 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
567 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
568
569 ppr_defn loc | isGoodSrcLoc loc = ptext SLIT("at") <+> ppr loc
570              | otherwise        = empty
571 \end{code}