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