[Haskell-cafe] instance monad problem

Stefan Holdermans stefan at cs.uu.nl
Tue May 15 00:25:09 EDT 2007


Veer,

> I get this error on ghci  :
> {-
> `a' is not applied to enough type arguments
>    Expected kind `*', but `a' has kind `* -> *'
>    In the type `SS a'
>    In the type `(Monad a) => {Monad (SS a)}'
>    In the instance declaration for `Monad (SS a)'
> -}

So, what you are running into is not as much a type error; it's a  
kind error. Kinds give structure to types, in the same way as types  
give structure to values. For instance,

   [Int]

and

   [Maybe Int]

are both well-formed types, but

   [Maybe]

is not: Maybe still expects a type argument. Now, let's have a look  
at kinds.

Int is a well-formed type in its own right; we say that it has kind  
*. (* is pronounced as 'type' or sometimes as 'star'). The type of  
lists, however, [], is to be applied to a type argument in order to  
form a well-formed type: so [] has kind * -> *. The same holds for  
Maybe: it requires a type argument and so it has kind * -> *.  
Summarizing:

   Int   ::      *
   []    :: * -> *
   Maybe :: * -> *

Now, why is [Maybe] not well-formed? Recall: [] has kind * -> *, so  
it expects a type argument of kind *. Here, we have supplied as type  
argument Maybe, which has kind * -> *. (Indeed, [Maybe] is just sugar  
for [] Maybe.) So, the kind do not match and we are confronted with a  
kind error.

Over to your code snippet.

> data SS a = SS a Int

Your type constructor SS expects a single type argument, so we have

   SS :: * -> *

Instances of the Monad type class are to have kind * -> * (for  
instance, [], Maybe, IO, ...); so, in terms of kinds, SS is a good  
candidate instance of Monad. But then:

> instance (Monad a)=> Monad (SS a) where

Let's see. SS had kind * -> *. This implies that, for SS a to be well- 
kinded, the type argument a is to be of kind *. But instances of  
Monad are of kind * -> * and you writing  Monad a in the instance  
head, implies that the type variable a had kind * -> *. Of course,  
the variable a cannot be of both kind * and kind * -> *. Hence, GHCi  
nicely presents you a kind error.

How to get out of this misery? I'd say, just get rid of the instance  
head:

   instance Monad SS where
     return x     = SS x 0
     SS x m >>= f = let ~(SS y n) = f x in SS y (m + n)

or

   instance Monad SS where
     return x     = SS x 1
     SS x m >>= f = let ~(SS y n) = f x in SS y (m * n)

HTH,

   Stefan


More information about the Haskell-Cafe mailing list