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

On branch  : ghc-kinds

http://hackage.haskell.org/trac/ghc/changeset/e695fb1e1e3c6c124b4cd803be07614f54a1e43f

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

commit e695fb1e1e3c6c124b4cd803be07614f54a1e43f
Author: Julien Cretin <g...@ia0.eu>
Date:   Wed Sep 21 15:00:38 2011 +0200

    fix scoping in desugarer in tcHsInstHead

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

 compiler/typecheck/TcHsType.lhs |   16 ++++++++--------
 1 files changed, 8 insertions(+), 8 deletions(-)

diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs
index 2ab51fe..cb86904 100644
--- a/compiler/typecheck/TcHsType.lhs
+++ b/compiler/typecheck/TcHsType.lhs
@@ -186,21 +186,21 @@ tcHsInstHead (L loc hs_ty)
   where
     kc_ds_inst_head ty = case splitHsClassTy_maybe cls_ty of
         Just _ -> do -- Kind-checking first
-          (tvs, ctxt, cls_ty) <- kcHsTyVars tv_names $ \ tv_names' -> do
-            ctxt' <- mapM kcHsLPredType ctxt
-            cls_ty' <- kc_check_hs_type cls_ty ekConstraint
+        { (tvs, ctxt, cls_ty) <- kcHsTyVars tv_names $ \ tv_names' -> do
+            { ctxt' <- mapM kcHsLPredType ctxt
+            ; cls_ty' <- kc_check_hs_type cls_ty ekConstraint
                -- The body of a forall is usually lifted, but in an instance
                -- head we only allow something of kind Constraint.
-            return (tv_names', ctxt', cls_ty')
+            ; return (tv_names', ctxt', cls_ty') }
           -- Now desugar the kind-checked type
-          cls_ty' <- ds_type cls_ty
-          let Just (tc, tys) = splitTyConApp_maybe cls_ty'
-          tcTyVarBndrs tvs  $ \ tvs' -> do
+        ; tcTyVarBndrs tvs  $ \ tvs' -> do
+            cls_ty' <- ds_type cls_ty
+            let Just (tc, tys) = splitTyConApp_maybe cls_ty'
             ctxt' <- dsHsTypes ctxt
             clas <- case tyConClass_maybe tc of
                       Just clas -> return clas
                       Nothing -> failWithTc (ppr tc <+> ptext (sLit "is not a 
class"))
-            return (tvs', ctxt', clas, tys)
+            return (tvs', ctxt', clas, tys) }
         _ -> failWithTc (ptext (sLit "Malformed instance type"))
       where (tv_names, ctxt, cls_ty) = splitHsForAllTy ty
 



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to