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:[EMAIL PROTECTED]
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                                 [EMAIL PROTECTED]
>
>

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to