<br><div class="gmail_quote">On Sun, Jun 27, 2010 at 6:25 AM, Max Bolingbroke <span dir="ltr">&lt;<a href="mailto:batterseapower@hotmail.com">batterseapower@hotmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
By the way, you can use this stuff to solve the restricted monad<br>
problem (e.g. make Set an instance of Monad). This is not that useful<br>
until we find out what the mother of all MonadPlus is, though, because<br>
we really need a MonadPlus Set instance.<br>
<br>
Code below.<br>
<br>
Cheers,<br>
Max<br>
<br>
\begin{code}<br>
{-# LANGUAGE RankNTypes #-}<br>
import Control.Applicative<br>
<br>
import Data.Set (Set)<br>
import qualified Data.Set as S<br>
<br>
<br>
newtype CodensityOrd m a = CodensityOrd { runCodensityOrd :: forall b.<br>
Ord b =&gt; (a -&gt; m b) -&gt; m b }<br>
<br>
-- liftCodensityOrd :: Monad m =&gt; m a -&gt; CodensityOrd m a<br>
-- liftCodensityOrd m = CodensityOrd ((&gt;&gt;=) m)<br>
<br>
-- lowerCodensityOrd :: (Ord a, Monad m) =&gt; CodensityOrd m a -&gt; m a<br>
-- lowerCodensityOrd m = runCodensityOrd m return<br>
<br>
instance Functor (CodensityOrd f) where<br>
    fmap f m = CodensityOrd (\k -&gt; runCodensityOrd m (k . f))<br>
<br>
instance Applicative (CodensityOrd f) where<br>
    pure x = CodensityOrd (\k -&gt; k x)<br>
    mf &lt;*&gt; mx = CodensityOrd (\k -&gt; runCodensityOrd mf (\f -&gt;<br>
runCodensityOrd mx (\x -&gt; k (f x))))<br>
<br>
instance Monad (CodensityOrd f) where<br>
    return = pure<br>
    m &gt;&gt;= k = CodensityOrd (\c -&gt; runCodensityOrd m (\a -&gt;<br>
runCodensityOrd (k a) c))<br>
<br>
<br>
<br>
liftSet :: Ord a =&gt; Set a -&gt; CodensityOrd Set a<br>
liftSet m = CodensityOrd (bind m)<br>
    where bind :: (Ord a, Ord b) =&gt; Set a -&gt; (a -&gt; Set b) -&gt; Set b<br>
          mx `bind` fxmy = S.fold (\x my -&gt; fxmy x `S.union` my) S.empty mx<br>
<br>
lowerSet :: Ord a =&gt; CodensityOrd Set a -&gt; Set a<br>
lowerSet m = runCodensityOrd m S.singleton<br>
<br>
<br>
main = print $ lowerSet $ monadicPlus (liftSet $ S.fromList [1, 2, 3])<br>
(liftSet $ S.fromList [1, 2, 3])<br>
<br>
monadicPlus :: Monad m =&gt; m Int -&gt; m Int -&gt; m Int<br>
monadicPlus mx my = do<br>
    x &lt;- mx<br>
    y &lt;- my<br>
    return (x + y)<br>
<br>
\end{code}<br>
<div><div></div><div class="h5"></div></div></blockquote><div><br></div>I&#39;ve pointed out the Codensity Set monad on the Haskell channel. It is an interesting novelty, but it unfortunately has somewhat funny semantics in that the intermediate sets that you obtain are based on what you would get if you reparenthesized all of your binds and associating them to the right.</div>
<div class="gmail_quote"><br></div><div class="gmail_quote">One way to think about how Codensity adjusts a monad is that it can take something that is almost a monad (you need to get in and out of Codensity). Another thing to note is that Codensity is slightly more powerful than the original type you embedded.</div>
<div class="gmail_quote"><br></div><div class="gmail_quote">An interesting example is that you can show that Codensity Reader ~ State. Take a look at the code in monad-ran on hackage for how Ran (StateT s m) is implemented for an example.</div>
<div class="gmail_quote"><br></div><div class="gmail_quote">-Edward Kmett</div>