<div>I discovered them and bundled them up a year or so back in category-extras.</div>
<div> </div>
<div><a href="http://comonad.com/haskell/category-extras/dist/doc/html/category-extras/Control-Monad-Codensity.html">http://comonad.com/haskell/category-extras/dist/doc/html/category-extras/Control-Monad-Codensity.html</a></div>

<div> </div>
<div>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.</div>
<div> </div>
<div><a href="http://comonad.com/reader/2008/kan-extensions/">http://comonad.com/reader/2008/kan-extensions/</a></div>
<div><a href="http://comonad.com/reader/2008/kan-extensions-ii/">http://comonad.com/reader/2008/kan-extensions-ii/</a></div>
<div><a href="http://comonad.com/reader/2008/kan-extension-iii/">http://comonad.com/reader/2008/kan-extension-iii/</a></div>
<div> </div>
<div>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.</div>

<div> </div>
<div>-Edward Kmett</div>
<div> </div>
<div class="gmail_quote">On Wed, Apr 8, 2009 at 2:22 PM, Sebastian Fischer <span dir="ltr">&lt;<a href="mailto:sebf@informatik.uni-kiel.de">sebf@informatik.uni-kiel.de</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="PADDING-LEFT: 1ex; MARGIN: 0px 0px 0px 0.8ex; BORDER-LEFT: #ccc 1px solid">&gt; {-# LANGUAGE Rank2Types #-}<br><br>Dear Haskellers,<br><br>I just realized that we get instances of `Monad` from pointed functors<br>
and instances of `MonadPlus` from alternative functors.<br><br>Is this folklore?<br><br>&gt; import Control.Monad<br>&gt; import Control.Applicative<br><br>In fact, every unary type constructor gives rise to a monad by the<br>
continuation monad transformer.<br><br>&gt; newtype ContT t a = ContT { unContT :: forall r . (a -&gt; t r) -&gt; t r }<br>&gt;<br>&gt; instance Monad (ContT t)<br>&gt;  where<br>&gt;   return x = ContT ($x)<br>&gt;   m &gt;&gt;= f  = ContT (\k -&gt; unContT m (\x -&gt; unContT (f x) k))<br>
<br>Both the `mtl` package and the `transformers` package use the same<br>`Monad` instance for their `ContT` type but require `t` to be an<br>instance of `Monad`. Why? [^1]<br><br>If `f` is an applicative functor (in fact, a pointed functor is<br>
enough), then we can translate monadic actions back to the original<br>type.<br><br>&gt; runContT :: Applicative f =&gt; ContT f a -&gt; f a<br>&gt; runContT m = unContT m pure<br><br>If `f` is an alternative functor, then `ContT f` is a `MonadPlus`.<br>
<br>&gt; instance Alternative f =&gt; MonadPlus (ContT f)<br>&gt;  where<br>&gt;   mzero       = ContT (const empty)<br>&gt;   a `mplus` b = ContT (\k -&gt; unContT a k &lt;|&gt; unContT b k)<br><br>That is no surprise because `empty` and `&lt;|&gt;` are just renamings for<br>
`mzero` and `mplus` (or the other way round). The missing piece was<br>`&gt;&gt;=` which is provided by `ContT` for free.<br><br>Are these instances defined somewhere?<br><br>Cheers,<br>Sebastian<br><br>[^1] I recognized that Janis Voigtlaender defines the type `ContT`<br>
under the name `C` in Section 3 of his paper on &quot;Asymptotic<br>Improvement of Computations over Free Monads&quot; (available at<br><a href="http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf" target="_blank">http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf</a>) and gives a monad<br>
instance without constraints on the first parameter.<br><br>_______________________________________________<br>Haskell-Cafe mailing list<br><a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br></blockquote></div><br>