Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : ghc-7.6

http://hackage.haskell.org/trac/ghc/changeset/1b6815c6ff197667af49c89edd2cf43af5276aa9

>---------------------------------------------------------------

commit 1b6815c6ff197667af49c89edd2cf43af5276aa9
Author: Simon Peyton Jones <[email protected]>
Date:   Sun Sep 9 07:07:39 2012 +0100

    Remember to zonk the skolems of an implication
    
    Their kinds may contain kind unification variables!
    
    This patch fixes Trac #7230.

>---------------------------------------------------------------

 compiler/typecheck/TcMType.lhs |   25 ++++++++++++++++++-------
 1 files changed, 18 insertions(+), 7 deletions(-)

diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index 411d85a..67ed967 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -593,14 +593,17 @@ skolemiseSigTv tv
 
 \begin{code}
 zonkImplication :: Implication -> TcM Implication
-zonkImplication implic@(Implic { ic_given = given 
+zonkImplication implic@(Implic { ic_skols  = skols
+                               , ic_given = given 
                                , ic_wanted = wanted
                                , ic_loc = loc })
-  = do {    -- No need to zonk the skolems
+  = do { skols'  <- mapM zonkTcTyVarBndr skols  -- Need to zonk their kinds!
+                                                -- as Trac #7230 showed
        ; given'  <- mapM zonkEvVar given
        ; loc'    <- zonkGivenLoc loc
        ; wanted' <- zonkWC wanted
-       ; return (implic { ic_given = given'
+       ; return (implic { ic_skols = skols'
+                        , ic_given = given'
                         , ic_wanted = wanted'
                         , ic_loc = loc' }) }
 
@@ -765,10 +768,18 @@ zonkTcType ty
                       | otherwise       = TyVarTy <$> updateTyVarKindM go tyvar
                -- Ordinary (non Tc) tyvars occur inside quantified types
 
-    go (ForAllTy tyvar ty) = ASSERT2( isImmutableTyVar tyvar, ppr tyvar ) do
-                             ty' <- go ty
-                             tyvar' <- updateTyVarKindM go tyvar
-                             return (ForAllTy tyvar' ty')
+    go (ForAllTy tv ty) = do { tv' <- zonkTcTyVarBndr tv
+                             ; ty' <- go ty
+                             ; return (ForAllTy tv' ty') }
+
+zonkTcTyVarBndr :: TcTyVar -> TcM TcTyVar
+-- A tyvar binder is never a unification variable (MetaTv),
+-- rather it is always a skolems.  BUT it may have a kind 
+-- that has not yet been zonked, and may include kind
+-- unification variables.
+zonkTcTyVarBndr tyvar
+  = ASSERT2( isImmutableTyVar tyvar, ppr tyvar ) do
+    updateTyVarKindM zonkTcType tyvar
 
 zonkTcTyVar :: TcTyVar -> TcM TcType
 -- Simply look through all Flexis



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to