What are Kind errors and how do you fix them?

Implementing Reverse from before, I am running into this weird error: type ReverseType a string = (string ->(string,a)) data Reverse a string = Reverse (ReverseType a string) instance Monad (Reverse a s) where return x = Reverse (\text -> (text,x)) (Reverse p) >>= k = Reverse p3 where p3 s0 = p2 s1 where (Reverse p2) = k a (s1,a)=p s0 Produces the error: Kind error: Expecting kind `* -> *', but `Reverse a s' has kind `*' When checking kinds in `Monad (Reverse a s)' In the instance declaration for `Monad (Reverse a s)' I have no clue what this error message means. -Alex- _________________________________________________________________ S. Alexander Jacobson mailto:me@alexjacobson.com tel:917-770-6565 http://alexjacobson.com

On 2004-03-23 at 16:58EST "S. Alexander Jacobson" wrote:
Implementing Reverse from before, I am running into this weird error:
type ReverseType a string = (string ->(string,a)) data Reverse a string = Reverse (ReverseType a string)
instance Monad (Reverse a s) where return x = Reverse (\text -> (text,x)) (Reverse p) >>= k = Reverse p3 where p3 s0 = p2 s1 where (Reverse p2) = k a (s1,a)=p s0
Produces the error:
Kind error: Expecting kind `* -> *', but `Reverse a s' has kind `*' When checking kinds in `Monad (Reverse a s)' In the instance declaration for `Monad (Reverse a s)'
I have no clue what this error message means.
Kinds are to types what types are to values. You've declared Reverse to have two arguments: it takes a type, then another type and returns a type, so its kind is * -> * -> *. (Reverse a) has kind * -> * and (Reverse a s) has kind *. Now a monad is something that takes a type as an argument, so has kind * -> *, for example IO has kind * -> * -- you expect to see IO Something most places. So (Reverse a) could perhaps be a monad, but (Reverse a s) cannot be. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

So if I want to use Monad, I have to have Reverse only work with Strings and not some data type that might be a String? Is there a workaround that would allow me to preserve flexibility around the target datatype? Otherwise I'll rename Forward and Reverse to toString and fromString, but the notion of being able to guarantee a roundtrip in and out of an arbitrary datatype seems useful and powerful. -Alex- On Tue, 23 Mar 2004, Jon Fairbairn wrote:
On 2004-03-23 at 16:58EST "S. Alexander Jacobson" wrote:
Implementing Reverse from before, I am running into this weird error:
type ReverseType a string = (string ->(string,a)) data Reverse a string = Reverse (ReverseType a string)
instance Monad (Reverse a s) where return x = Reverse (\text -> (text,x)) (Reverse p) >>= k = Reverse p3 where p3 s0 = p2 s1 where (Reverse p2) = k a (s1,a)=p s0
Produces the error:
Kind error: Expecting kind `* -> *', but `Reverse a s' has kind `*' When checking kinds in `Monad (Reverse a s)' In the instance declaration for `Monad (Reverse a s)'
I have no clue what this error message means.
Kinds are to types what types are to values. You've declared Reverse to have two arguments: it takes a type, then another type and returns a type, so its kind is * -> * -> *. (Reverse a) has kind * -> * and (Reverse a s) has kind *.
Now a monad is something that takes a type as an argument, so has kind * -> *, for example IO has kind * -> * -- you expect to see IO Something most places. So (Reverse a) could perhaps be a monad, but (Reverse a s) cannot be.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
_________________________________________________________________ S. Alexander Jacobson mailto:me@alexjacobson.com tel:917-770-6565 http://alexjacobson.com

Ok, I am still trying to understand kind errors and now have a very simple class and types: class MyClass a b where emptyVal::a b type MyType a = [a] type MyType2 = [] I can't figure out why some instance work and others don't. e.g. this one works: instance MyClass MyType2 a where emptyVal=[] But this one doesn't: instance MyClass (MyType a) a where emptyVal=[] and neither does this one: instance MyClass (MyType) a where emptyVal=[] How do I make (MyType a) work? For example, a real world example is: type MyType a = FiniteMap a String? -Alex- _________________________________________________________________ S. Alexander Jacobson mailto:me@alexjacobson.com tel:917-770-6565 http://alexjacobson.com On Tue, 23 Mar 2004, Jon Fairbairn wrote:
On 2004-03-23 at 16:58EST "S. Alexander Jacobson" wrote:
Implementing Reverse from before, I am running into this weird error:
type ReverseType a string = (string ->(string,a)) data Reverse a string = Reverse (ReverseType a string)
instance Monad (Reverse a s) where return x = Reverse (\text -> (text,x)) (Reverse p) >>= k = Reverse p3 where p3 s0 = p2 s1 where (Reverse p2) = k a (s1,a)=p s0
Produces the error:
Kind error: Expecting kind `* -> *', but `Reverse a s' has kind `*' When checking kinds in `Monad (Reverse a s)' In the instance declaration for `Monad (Reverse a s)'
I have no clue what this error message means.
Kinds are to types what types are to values. You've declared Reverse to have two arguments: it takes a type, then another type and returns a type, so its kind is * -> * -> *. (Reverse a) has kind * -> * and (Reverse a s) has kind *.
Now a monad is something that takes a type as an argument, so has kind * -> *, for example IO has kind * -> * -- you expect to see IO Something most places. So (Reverse a) could perhaps be a monad, but (Reverse a s) cannot be.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Fri, 2004-03-26 at 20:08, S. Alexander Jacobson wrote:
Ok, I am still trying to understand kind errors and now have a very simple class and types:
class MyClass a b where emptyVal::a b
type MyType a = [a] type MyType2 = []
Let me rename some type variables here: class MyClass c d where emptyVal::c d type MyType a = [a] type MyType2 = []
I can't figure out why some instance work and others don't. e.g. this one works:
instance MyClass MyType2 a where emptyVal=[]
But this one doesn't:
instance MyClass (MyType a) a where emptyVal=[]
instance MyClass (MyType b) b where emptyVal=[] Here, you are matching the class declaration (MyClass c d) against the instance declaration (MyClass (MyType b) b); this matches with c == MyType b d == b Then you claim that emptyVal=[] has type (c d), which is type (MyType b b); so you are using MyType as a type constructor with two type arguments. But MyType only takes one type argument, so this is an illegal type.
and neither does this one:
instance MyClass (MyType) a where emptyVal=[]
This is a different problem. Here, you have defined a type synonym MyType which takes one argument, but you have not provided it any arguments. Type synonyms cannot be used this way; they are sort of like macros, and the first step is macroexpansion -- so you are trying to use a macro without providing the necessary arguments. <technical note> There are good technical reasons for the requirement that type synonyms must always be fully applied. Here's just one example of the sort of trouble you run into without this requirement: Suppose you have a function f :: a Int -> a Float And suppose you have type synonyms: type Pairii a = (Int, Int) type Pairia a = (Int, a) type Pairaa a = (a, a) What is the type of (f (3::Int,3::Int))? Well, (3::Int,3::Int) has type (Int,Int); this is the same as Pairii Int, so the result has type Pairii Float which is (Int,Int). But (Int,Int) is also the same as Pairia Int, so the result has type Pairia Float which is (Int,Float); and (Int,Int) is Pairaa Int, so the result has type Pairaa Float which is (Float,Float). Haskell avoids this dilemma by not treating Pairii, Pairia, and Pairaa as first-class type constructors, so they can't match a in (a Int). By the way: the 2-tuple type constructor, (,), is a first-class type constructor; so the type (Int,Int) is the same as (((,) Int) Int); this matches (a Int) with a being ((,) Int), so the result type of the above expression is ((,) Int Float) or (Int,Float).
How do I make (MyType a) work? For example, a real world example is:
type MyType a = FiniteMap a String?
I hope you understand the kind error, and why (MyType a) is not what you want. To get an instance for MyClass MyType a, you'll need to make MyType a first-class type constructor. You can get first-class type constructors with newtype (at the cost of having a constructor for the type); the following works: newtype MyType a = Make_MyType [a] instance MyClass MyType a where emptyVal=Make_MyType [] Carl Witty

I want to thank everybody for the kind explanations of kind errors. I think I now understand them (figured it out through a LOT of trial and error). The problem (as Carl and others noted) was I was testing various ways of doing things using synonyms rather than data types and didn't know that you can't do that! Based on my recent experience as a new coder, here are some words of advice for future beginners: * Beware the monomorphism restriction! * Avoid type synonyms in instance declarations! * use newtype whenever possible (also see quickcheck docs) * you can't use existential types except through class methods! * you must wrap existential types if you want to use them in record-style data declarations (No, I have no idea why this is, but it appears to be true nonetheless) The problem with this sort of list is that it is probably only useful after you have already made these mistakes. Oh well. -Alex- _________________________________________________________________ S. Alexander Jacobson mailto:me@alexjacobson.com tel:917-770-6565 http://alexjacobson.com

Alex, AJ> Ok, I am still trying to understand kind errors and now have AJ> a very simple class and types: Okay, let's have a look. You declare
class MyClass a b where emptyVal :: a b
In the type signature for emptyVal the type variable a is applied to b. So, we infer a :: k -> l b :: k for kinds k and l. Applying the default binding k = * to k and l (so that k = * and l = *) yields a :: * -> * b :: * So far, so good. Then you declare
type MyType a = [a] type MyType2 = []
Since [] :: * -> *, we infer MyType :: * -> * MyType2 :: * -> * Then you write
instance MyClass MyType2 b where emptyVal = []
(For clarity, I write b where you used a.) Recall that we inferred that the first argument (a) of MyClass should have kind * -> *, while the second argument (b) should have kind *. Here, you've substituted MyType2 :: * -> * for a. So the kinds match and everything is okay. But then:
instance MyClass (MyType b) b where emptyVal = []
The second argument (b) should have kind *. Since, no further information is available, we thus assume b :: *. MyType has kind * -> * and is applied to b; so, (MyType b) :: *. However, we expected the first argument of MyClass to have kind * -> *. So, this instance declaration won't compile. When you write
instance MyClass MyType b where emptyVal= []
the kinds are okay, but this won't compile since type synonyms are not allowed to be applied partially. Finally, assuming FiniteMap :: * -> * -> *, from
type StringMap a = FiniteMap a String
we infer StringMap :: * -> *. Since, synonyms have to be applied fully, you can only substitute StringMap for the second argument of MyClass. HTH, Stefan
-----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of S. Alexander Jacobson Sent: Saturday, March 27, 2004 5:09 AM To: Jon Fairbairn Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] What are Kind errors and how do you fix them?
Ok, I am still trying to understand kind errors and now have a very simple class and types:
class MyClass a b where emptyVal::a b
type MyType a = [a] type MyType2 = []
I can't figure out why some instance work and others don't. e.g. this one works:
instance MyClass MyType2 a where emptyVal=[]
But this one doesn't:
instance MyClass (MyType a) a where emptyVal=[]
and neither does this one:
instance MyClass (MyType) a where emptyVal=[]
How do I make (MyType a) work? For example, a real world example is:
type MyType a = FiniteMap a String?
-Alex-
_________________________________________________________________ S. Alexander Jacobson mailto:me@alexjacobson.com tel:917-770-6565 http://alexjacobson.com
On Tue, 23 Mar 2004, Jon Fairbairn wrote:
On 2004-03-23 at 16:58EST "S. Alexander Jacobson" wrote:
Implementing Reverse from before, I am running into this weird error:
type ReverseType a string = (string ->(string,a)) data Reverse a string = Reverse (ReverseType a string)
instance Monad (Reverse a s) where return x = Reverse (\text -> (text,x)) (Reverse p) >>= k = Reverse p3 where p3 s0 = p2 s1 where (Reverse p2) = k a (s1,a)=p s0
Produces the error:
Kind error: Expecting kind `* -> *', but `Reverse a s' has kind `*' When checking kinds in `Monad (Reverse a s)' In the instance declaration for `Monad (Reverse a s)'
I have no clue what this error message means.
Kinds are to types what types are to values. You've declared Reverse to have two arguments: it takes a type, then another type and returns a type, so its kind is * -> * -> *. (Reverse a) has kind * -> * and (Reverse a s) has kind *.
Now a monad is something that takes a type as an argument, so has kind * -> *, for example IO has kind * -> * -- you expect to see IO Something most places. So (Reverse a) could perhaps be a monad, but (Reverse a s) cannot be.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Carl Witty
-
Jon Fairbairn
-
S. Alexander Jacobson
-
S. Alexander Jacobson
-
Stefan Holdermans