
I discovered them and bundled them up a year or so back in category-extras. http://comonad.com/haskell/category-extras/dist/doc/html/category-extras/Con... I also wrote a series of blog posts including the derivation of these and their dual in the form of right- and left- Kan extensions. http://comonad.com/reader/2008/kan-extensions/ http://comonad.com/reader/2008/kan-extensions-ii/ http://comonad.com/reader/2008/kan-extension-iii/ I shared with Janis Voigtlaender the connection to his asymptotic improvement in the performance of free monads paper as well. After I discovered the connection between these and that paper shortly thereafter. -Edward Kmett On Wed, Apr 8, 2009 at 2:22 PM, Sebastian Fischer < sebf@informatik.uni-kiel.de> 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]
If `f` is an applicative functor (in fact, a pointed functor is enough), then we can translate monadic actions back to the original type.
runContT :: Applicative f => ContT f a -> f a runContT m = unContT m pure
If `f` is an alternative functor, then `ContT f` is a `MonadPlus`.
instance Alternative f => MonadPlus (ContT f) where mzero = ContT (const empty) a `mplus` b = ContT (\k -> unContT a k <|> unContT b k)
That is no surprise because `empty` and `<|>` are just renamings for `mzero` and `mplus` (or the other way round). The missing piece was `>>=` which is provided by `ContT` for free.
Are these instances defined somewhere?
Cheers, Sebastian
[^1] I recognized that Janis Voigtlaender defines the type `ContT` under the name `C` in Section 3 of his paper on "Asymptotic Improvement of Computations over Free Monads" (available at http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf) and gives a monad instance without constraints on the first parameter.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe