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

On branch  : ghc-kinds

http://hackage.haskell.org/trac/ghc/changeset/11b67256e9e3949a2c5c60aa930f34edf895f2ce

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

commit 11b67256e9e3949a2c5c60aa930f34edf895f2ce
Author: Julien Cretin <g...@ia0.eu>
Date:   Fri Sep 23 00:47:11 2011 +0200

    kind signatures for hs-boot files

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

 compiler/TODO                         |    2 +-
 compiler/hsSyn/HsExpr.lhs-boot        |    6 +++---
 compiler/hsSyn/HsPat.lhs-boot         |    4 +++-
 compiler/typecheck/TcRnTypes.lhs-boot |    2 +-
 compiler/typecheck/TcRules.lhs        |    2 --
 compiler/types/Kind.lhs               |    2 +-
 6 files changed, 9 insertions(+), 9 deletions(-)

diff --git a/compiler/TODO b/compiler/TODO
index d7b3ce0..5903d71 100644
--- a/compiler/TODO
+++ b/compiler/TODO
@@ -1,6 +1,6 @@
 ## TODO FIRST
 
-* data declarations in hs-boot files will always need kind signatures
+* BUG: how to solve kind polymorphic boot files?
 
 * ds_type takes a flag
   - either it does defaulting: alpha -> star
diff --git a/compiler/hsSyn/HsExpr.lhs-boot b/compiler/hsSyn/HsExpr.lhs-boot
index 275a9f6..650e3ba 100644
--- a/compiler/hsSyn/HsExpr.lhs-boot
+++ b/compiler/hsSyn/HsExpr.lhs-boot
@@ -9,9 +9,9 @@ import {-# SOURCE #-} HsPat  ( LPat )
 import Data.Data
        
 data HsExpr (i :: *)
-data HsSplice i
-data MatchGroup a
-data GRHSs a
+data HsSplice (i :: *)
+data MatchGroup (a :: *)
+data GRHSs (a :: *)
 
 instance Typeable1 HsSplice
 instance Data i => Data (HsSplice i)
diff --git a/compiler/hsSyn/HsPat.lhs-boot b/compiler/hsSyn/HsPat.lhs-boot
index 7ba338e..93b1251 100644
--- a/compiler/hsSyn/HsPat.lhs-boot
+++ b/compiler/hsSyn/HsPat.lhs-boot
@@ -1,10 +1,12 @@
 \begin{code}
+{-# LANGUAGE KindSignatures #-}
+
 module HsPat where
 import SrcLoc( Located )
 
 import Data.Data
 
-data Pat i
+data Pat (i :: *)
 type LPat i = Located (Pat i)
 
 instance Typeable1 Pat
diff --git a/compiler/typecheck/TcRnTypes.lhs-boot 
b/compiler/typecheck/TcRnTypes.lhs-boot
index 36c43fc..b16446b 100644
--- a/compiler/typecheck/TcRnTypes.lhs-boot
+++ b/compiler/typecheck/TcRnTypes.lhs-boot
@@ -7,7 +7,7 @@ type TcM a = TcRn a
 type TcRn a = TcRnIf TcGblEnv TcLclEnv a
 type TcRnIf a b c = IOEnv (Env a b) c
 
-data Env a b
+data Env (a :: *) (b :: *)
 data TcGblEnv
 data TcLclEnv
 \end{code}
diff --git a/compiler/typecheck/TcRules.lhs b/compiler/typecheck/TcRules.lhs
index f6cd420..ed50509 100644
--- a/compiler/typecheck/TcRules.lhs
+++ b/compiler/typecheck/TcRules.lhs
@@ -54,7 +54,6 @@ tcRule (HsRule name act hs_bndrs lhs fv_lhs rhs fv_rhs)
        -- Note [Typechecking rules]
        ; vars <- tcRuleBndrs hs_bndrs
        ; let (id_bndrs, tv_bndrs) = partition isId vars
-       ; traceTc "IA0_DEBUG tv_bndrs" (ppr tv_bndrs)
        ; (lhs', lhs_lie, rhs', rhs_lie, rule_ty)
             <- tcExtendTyVarEnv tv_bndrs $
                tcExtendIdEnv id_bndrs $
@@ -96,7 +95,6 @@ tcRule (HsRule name act hs_bndrs lhs fv_lhs rhs fv_rhs)
                                       `minusVarSet` gbl_tvs
                                       `delVarSetList` tv_bndrs
        ; qtvs <- zonkQuantifiedTyVars (varSetElems extra_bound_tvs)
-       ; traceTc "IA0_DEBUG qtvs" (ppr qtvs)
 
                      -- The tv_bndrs are already skolems, so no need to zonk 
them
        ; return (HsRule name act
diff --git a/compiler/types/Kind.lhs b/compiler/types/Kind.lhs
index be23b10..ca7e08a 100644
--- a/compiler/types/Kind.lhs
+++ b/compiler/types/Kind.lhs
@@ -197,7 +197,7 @@ isSubKind (TyConApp kc1 k1s) (TyConApp kc2 k2s)
     kc1 == kc2 && length k1s == length k2s && all (uncurry eqKind) (zip k1s 
k2s)
 
   | isSuperKindTyCon kc1 =  -- handles BOX
-    ASSERT( isSuperKindTyCon kc2 && null k1s && null k2s )
+    ASSERT2( isSuperKindTyCon kc2 && null k1s && null k2s, ppr kc1 <+> ppr kc2 
)
     True
 
   | otherwise =  -- handles not promoted kinds (*, #, (#), etc.)



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

Reply via email to