[commit: ghc] master: When quantifying associated types, we may have TyVars involved, not just TcTyVars (6464d37)
Simon Peyton Jones
simonpj at microsoft.com
Tue Jan 29 13:50:34 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/ghc
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/6464d377b85c1b20a2bfb29eb579e88f36bce333
>---------------------------------------------------------------
commit 6464d377b85c1b20a2bfb29eb579e88f36bce333
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jan 29 08:57:05 2013 +0000
When quantifying associated types, we may have TyVars involved, not just TcTyVars
This required a little adjustment in zonkQuantifiedTyVars
>---------------------------------------------------------------
compiler/typecheck/TcHsType.lhs | 8 ++++----
compiler/typecheck/TcMType.lhs | 13 +++++++++++--
2 files changed, 15 insertions(+), 6 deletions(-)
diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs
index cd5e029..69b97ce 100644
--- a/compiler/typecheck/TcHsType.lhs
+++ b/compiler/typecheck/TcHsType.lhs
@@ -886,7 +886,7 @@ tcScopedKindVars kv_ns thing_inside
= tcExtendTyVarEnv (map mkKindSigVar kv_ns) thing_inside
tcHsTyVarBndrs :: LHsTyVarBndrs Name
- -> ([TyVar] -> TcM r)
+ -> ([TcTyVar] -> TcM r)
-> TcM r
-- Bind the type variables to skolems, each with a meta-kind variable kind
tcHsTyVarBndrs (HsQTvs { hsq_kvs = kvs, hsq_tvs = hs_tvs }) thing_inside
@@ -895,7 +895,7 @@ tcHsTyVarBndrs (HsQTvs { hsq_kvs = kvs, hsq_tvs = hs_tvs }) thing_inside
; traceTc "tcHsTyVarBndrs" (ppr hs_tvs $$ ppr tvs)
; tcExtendTyVarEnv tvs (thing_inside tvs) }
-tcHsTyVarBndr :: LHsTyVarBndr Name -> TcM TyVar
+tcHsTyVarBndr :: LHsTyVarBndr Name -> TcM TcTyVar
-- Return a type variable
-- initialised with a kind variable.
-- Typically the Kind inside the KindedTyVar will be a tyvar with a mutable kind
@@ -907,7 +907,7 @@ tcHsTyVarBndr :: LHsTyVarBndr Name -> TcM TyVar
-- instance C (a,b) where
-- type F (a,b) c = ...
-- Here a,b will be in scope when processing the associated type instance for F.
--- See Note [Associated type tyvar names] in TyCon
+-- See Note [Associated type tyvar names] in Class
tcHsTyVarBndr (L _ hs_tv)
= do { let name = hsTyVarName hs_tv
; mb_tv <- tcLookupLcl_maybe name
@@ -915,7 +915,7 @@ tcHsTyVarBndr (L _ hs_tv)
Just (ATyVar _ tv) -> return tv ;
_ -> do
{ kind <- case hs_tv of
- UserTyVar {} -> newMetaKindVar
+ UserTyVar {} -> newMetaKindVar
KindedTyVar _ kind -> tcLHsKind kind
; return (mkTcTyVar name kind (SkolemTv False)) } } }
diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index 8af1e4c..f0dd6e9 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -547,9 +547,12 @@ defaultKindVarToStar kv
zonkQuantifiedTyVars :: [TcTyVar] -> TcM [TcTyVar]
-- A kind variable k may occur *after* a tyvar mentioning k in its kind
+-- Can be given a mixture of TcTyVars and TyVars, in the case of
+-- associated type declarations
zonkQuantifiedTyVars tyvars
= do { let (kvs, tvs) = partition isKindVar tyvars
- (meta_kvs, skolem_kvs) = partition isMetaTyVar kvs
+ (meta_kvs, skolem_kvs)
+ = partition (\kv -> isTcTyVar kv && isMetaTyVar kv) kvs
-- In the non-PolyKinds case, default the kind variables
-- to *, and zonk the tyvars as usual. Notice that this
@@ -562,10 +565,16 @@ zonkQuantifiedTyVars tyvars
do { mapM_ defaultKindVarToStar meta_kvs
; return skolem_kvs } -- Should be empty
- ; mapM zonkQuantifiedTyVar (qkvs ++ tvs) }
+ ; mapM zonk_quant (qkvs ++ tvs) }
-- Because of the order, any kind variables
-- mentioned in the kinds of the type variables refer to
-- the now-quantified versions
+ where
+ zonk_quant tkv
+ | isTcTyVar tkv = zonkQuantifiedTyVar tkv
+ | otherwise = return tkv
+ -- For associated types, we have the class variables
+ -- in scope, and they are TyVars not TcTyVars
zonkQuantifiedTyVar :: TcTyVar -> TcM TcTyVar
-- The quantified type variables often include meta type variables
More information about the ghc-commits
mailing list