[Haskell-cafe] Re: Re: Monads from Functors

Ben Franksen ben.franksen at online.de
Wed Apr 8 19:24:19 EDT 2009


David Menendez wrote:
> On Wed, Apr 8, 2009 at 5:20 PM, Ben Franksen <ben.franksen at online.de>
> wrote:
>> Sebastian Fischer wrote:
>>> > {-# LANGUAGE Rank2Types #-}
>>>
>>> Dear Haskellers,
>>>
>>> I just realized that we get instances of `Monad` from pointed functors
>>> and instances of `MonadPlus` from alternative functors.
>>>
>>> Is this folklore?
>>>
>>> > import Control.Monad
>>> > import Control.Applicative
>>>
>>> In fact, every unary type constructor gives rise to a monad by the
>>> continuation monad transformer.
>>>
>>> > newtype ContT t a = ContT { unContT :: forall r . (a -> t r) -> t r }
>>> >
>>> > instance Monad (ContT t)
>>> >  where
>>> >   return x = ContT ($x)
>>> >   m >>= f  = ContT (\k -> unContT m (\x -> unContT (f x) k))
>>>
>>> Both the `mtl` package and the `transformers` package use the same
>>> `Monad` instance for their `ContT` type but require `t` to be an
>>> instance of `Monad`. Why? [^1]
>>
>> Maybe because this is needed to prove monad laws?
> 
> <snip derivation>
> 
>> So, that wasn't the reason. It really is a monad.
> 
> In general, ContT r m a is equivalent to Cont (m r) a, and their
> corresponding Monad instances are also equivalent. But Cont r is a
> monad for any r, which implies that ContT r m must be a monad for any
> r and m.

But it was a nice little exercise, right? :-)

BTW, is this (ContT t) somehow related to the 'free monad' over t?

Cheers
Ben



More information about the Haskell-Cafe mailing list