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

On branch  : ghc-kinds

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

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

commit e28223bbea8ee88f26fcf8bb3a0a0f3c97fd9a42
Author: Julien Cretin <g...@ia0.eu>
Date:   Wed Sep 14 11:51:34 2011 +0200

    handling kind polymorphism in check_type

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

 compiler/typecheck/TcMType.lhs |    9 +++------
 1 files changed, 3 insertions(+), 6 deletions(-)

diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index b40f1ef..40bc9be 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -930,7 +930,7 @@ check_type rank _ (AppTy ty1 ty2)
   = do { check_arg_type rank ty1
        ; check_arg_type rank ty2 }
 
-check_type rank ubx_tup ty@(TyConApp tc tys)
+check_type rank ubx_tup ty@(TyConApp tc tys')
   | isSynTyCon tc
   = do {       -- Check that the synonym has enough args
                -- This applies equally to open and closed synonyms
@@ -963,15 +963,12 @@ check_type rank ubx_tup ty@(TyConApp tc tys)
                -- more unboxed tuples, so can't use check_arg_ty
        ; mapM_ (check_type rank' UT_Ok) tys }
 
-  -- IA0: check what follows
-  | isPromotedDataTyCon tc  -- tys contain kind instantiations first
-  = let (kvs, _) = splitForAllTys (tyConKind tc) in
-    mapM_ (check_arg_type rank) (drop (length kvs) tys)
-
   | otherwise
   = mapM_ (check_arg_type rank) tys
 
   where
+    (kvs, _) = splitForAllTys (tyConKind tc)  -- tys contain kind 
instantiation arguments
+    tys = drop (length kvs) tys'  -- IA0: Are there any checks to do on the 
kind arguments?
     ubx_tup_ok ub_tuples_allowed = case ubx_tup of
                                    UT_Ok -> ub_tuples_allowed
                                    _     -> False



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

Reply via email to