diff options
author | simonpj <unknown> | 2001-12-06 10:45:43 +0000 |
---|---|---|
committer | simonpj <unknown> | 2001-12-06 10:45:43 +0000 |
commit | 61fae1d3fb61c5f53c3fbcb94afe7c548ad31591 (patch) | |
tree | b6f7d88797610980dcf504be8f98328f817269f7 /ghc/compiler/rename/RnMonad.lhs | |
parent | 94cf74b8ae28075496a67c1a83df630bc6cabc7c (diff) | |
download | haskell-61fae1d3fb61c5f53c3fbcb94afe7c548ad31591.tar.gz |
[project @ 2001-12-06 10:45:42 by simonpj]
--------------------------
Fix the instance-decl wart
--------------------------
This commit implements the (proposed) H98 rule for
resolving the class-method name in an instance decl.
module M( C( op1, op2 ) ) where
-- NB: op3 not exported
class C a where
op1, op2, op3 :: a -> a
module N where
import qualified M as P( C )
import qualified M as Q hiding( op2 )
instance P.C Int where
op1 x = x
-- op2, op3 both illegal here
The point is that
a) only methods that can be named are legal
in the instance decl
(so op2, op3 are not legal)
b) but it doesn't matter *how* they can be named
(in this case Q.op1 is in scope, though
the class is called P.C)
The AvailEnv carries the information about what's in scope,
so we now have to carry it around in the monad, so that
instance decl bindings can see it. Quite simple really.
Same deal for export lists. E.g.
module N( P.C( op1 ) ) where
import qualified M as P( C )
import qualified M as Q hiding( op2 )
Actually this is what GHC has always implemented!
Diffstat (limited to 'ghc/compiler/rename/RnMonad.lhs')
-rw-r--r-- | ghc/compiler/rename/RnMonad.lhs | 30 |
1 files changed, 22 insertions, 8 deletions
diff --git a/ghc/compiler/rename/RnMonad.lhs b/ghc/compiler/rename/RnMonad.lhs index 90de0eed71..495b50f961 100644 --- a/ghc/compiler/rename/RnMonad.lhs +++ b/ghc/compiler/rename/RnMonad.lhs @@ -36,7 +36,7 @@ import IO ( hPutStr, stderr ) import HsSyn import RdrHsSyn import RnHsSyn ( RenamedFixitySig ) -import HscTypes ( AvailEnv, lookupType, +import HscTypes ( AvailEnv, emptyAvailEnv, lookupType, NameSupply(..), ImportedModuleInfo, WhetherHasOrphans, ImportVersion, PersistentRenamerState(..), Avails, @@ -148,6 +148,13 @@ data SDown = SDown { rn_genv :: GlobalRdrEnv, -- Top level environment + rn_avails :: AvailEnv, + -- Top level AvailEnv; contains all the things that + -- are nameable in the top-level scope, regardless of + -- *how* they can be named (qualified, unqualified...) + -- It is used only to map a Class to its class ops, and + -- hence to resolve the binders in an instance decl + rn_lenv :: LocalRdrEnv, -- Local name envt -- Does *not* include global name envt; may shadow it -- Includes both ordinary variables and type variables; @@ -369,22 +376,24 @@ initRn dflags hit hst pcs mod do_rn return (new_pcs, (warns, errs), res) -initRnMS :: GlobalRdrEnv -> LocalRdrEnv -> LocalFixityEnv -> RnMode +initRnMS :: GlobalRdrEnv -> AvailEnv -> LocalRdrEnv -> LocalFixityEnv -> RnMode -> RnMS a -> RnM d a -initRnMS rn_env local_env fixity_env mode thing_inside rn_down g_down +initRnMS rn_env avails local_env fixity_env mode thing_inside rn_down g_down -- The fixity_env appears in both the rn_fixenv field -- and in the HIT. See comments with RnHiFiles.lookupFixityRn = let - s_down = SDown { rn_genv = rn_env, rn_lenv = local_env, - rn_fixenv = fixity_env, rn_mode = mode } + s_down = SDown { rn_genv = rn_env, rn_avails = avails, + rn_lenv = local_env, rn_fixenv = fixity_env, + rn_mode = mode } in thing_inside rn_down s_down initIfaceRnMS :: Module -> RnMS r -> RnM d r initIfaceRnMS mod thing_inside - = initRnMS emptyRdrEnv emptyRdrEnv emptyLocalFixityEnv InterfaceMode $ - setModuleRn mod thing_inside + = initRnMS emptyRdrEnv emptyAvailEnv emptyRdrEnv + emptyLocalFixityEnv InterfaceMode + (setModuleRn mod thing_inside) \end{code} @renameDerivedCode@ is used to rename stuff ``out-of-line''; @@ -420,8 +429,9 @@ renameDerivedCode dflags mod prs thing_inside rn_hit = bogus "rn_hit", rn_ifaces = bogus "rn_ifaces" } - ; let s_down = SDown { rn_mode = InterfaceMode, + ; let s_down = SDown { rn_mode = InterfaceMode, -- So that we can refer to PrelBase.True etc + rn_avails = emptyAvailEnv, rn_genv = emptyRdrEnv, rn_lenv = emptyRdrEnv, rn_fixenv = emptyLocalFixityEnv } @@ -689,6 +699,10 @@ getGlobalNameEnv :: RnMS GlobalRdrEnv getGlobalNameEnv rn_down (SDown {rn_genv = global_env}) = return global_env +getGlobalAvails :: RnMS AvailEnv +getGlobalAvails rn_down (SDown {rn_avails = avails}) + = return avails + setLocalNameEnv :: LocalRdrEnv -> RnMS a -> RnMS a setLocalNameEnv local_env' m rn_down l_down = m rn_down (l_down {rn_lenv = local_env'}) |