Various style at instance of a typeclass

The Control.Monad.Writer module exports the Writer w a type along with its Monad instance newtype Writer w a = Writer { runWriter :: (a, w) } instance (Monoid w) => Monad (Writer w) where return x = Writer (x, mempty) (Writer (x,v)) >>= f = let (Writer (y, v')) = f x in Writer (y, v `mappend` v') My question is Why the signature is "Monad (Write w)" but neither "Monad Write" nor "Monad (Write w a)"? Any difference among those three styles? Thanks a lot! -Haisheng

The class Monad is more specifically a "constructor class" rather than a type class. Constructor classes have particular arities (numbers of parameters - "holes") called "kinds". Monad is a constructor class with kind :: * -> * (Write w) - has kind :: * -> * Write - has kind :: * -> * -> * (Write w a) - has kind :: * Thus only the first is compatible with the Monad class.

Thanks Stephen. Your explanation is comprehensive.
Well, how did you know Monad is with kind :: * -> * ?
What about the Arrow (From Control.Arrow) class?
Did you have any references or something regarding such concepts?
-Haisheng
On Wed, Jun 29, 2011 at 10:21 PM, Stephen Tetley
The class Monad is more specifically a "constructor class" rather than a type class.
Constructor classes have particular arities (numbers of parameters - "holes") called "kinds".
Monad is a constructor class with kind :: * -> *
(Write w) - has kind :: * -> *
Write - has kind :: * -> * -> *
(Write w a) - has kind :: *
Thus only the first is compatible with the Monad class.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 29 June 2011 16:36, Haisheng Wu
Well, how did you know Monad is with kind :: * -> * ?
If I was looking at the docs I'd see these two pieces
class Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b
As (m a) and (m b) are used in the method (>>=) and but only m is specified in the class declaration, it would tell me m is :: * -> *. There is an extension in GHC (probably {-# LANGUAGE KindSignatures #-} ) where you can specify kinds in the class declaration:
class Monad (m :: * -> *) where
Personally I wouldn't be upset if this was the only valid syntax - it's redundant but I find it clearer. I'm not sure what references are available. I think constructor classes were originally implemented in Gofer (a Haskell variant) and when they were in Gofer but not Haskell, people seemed to make a clear distinction between the two. Nowadays people just call them "type classes" and have got used to the kinds of the common classes.
participants (2)
-
Haisheng Wu
-
Stephen Tetley