
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? Hm, let's try it. m >>= return = ContT (\k -> unContT m (\x -> unContT (return x) k)) = ContT (\k -> unContT m (\x -> unContT (ContT ($x)) k)) = ContT (\k -> unContT m (\x -> ($x) k)) = ContT (\k -> unContT m (\x -> k x)) = ContT (\k -> unContT m k) = ContT (unContT m) = m return x >>= f = ContT (\k -> unContT (return x) (\x' -> unContT (f x') k)) = ContT (\k -> unContT (ContT ($x)) (\x' -> unContT (f x') k)) = ContT (\k -> ($x) (\x' -> unContT (f x') k)) = ContT (\k -> (\x' -> unContT (f x') k) x) = ContT (\k -> unContT (f x) k) = ContT (unContT (f x)) = f x (m >>= f) >>= g = ContT (\k -> unContT m (\x -> unContT (f x) k)) >>= g = ContT (\q -> unContT (ContT (\k -> unContT m (\x -> unContT (f x) k))) (\y -> unContT (g y) q)) = ContT (\q -> (\k -> unContT m (\x -> unContT (f x) k)) (\y -> unContT (g y) q)) = ContT (\q -> unContT m (\x -> unContT (f x) (\y -> unContT (g y) q))) = ContT (\q -> unContT m (\x -> (\k -> unContT (f x) (\y -> unContT (g y) k)) q)) = ContT (\q -> unContT m (\x -> unContT (ContT (\k -> unContT (f x) (\y -> unContT (g y) k))) q)) = ContT (\q -> unContT m (\x -> unContT (f x >>= g) q)) = ContT (\q -> unContT m (\x -> unContT ((\y -> f y >>= g) x) q)) = m >>= (\y -> f y >>= g) Uff. So, that wasn't the reason. It really is a monad. Cheers Ben