+1, but to quibble, even for trivial things like this we usually try to allow at least 2 weeks for discussion.<div><br></div><div>Why not just import STRet from <a href="http://GHC.ST">GHC.ST</a> and exploit that rather than redefine it? Just curious -- I&#39;m not biased one way or the other.</div>
<div><br></div><div>-Edward<br><br><div class="gmail_quote">On Thu, Feb 17, 2011 at 8:57 AM, Sebastiaan Visser <span dir="ltr">&lt;<a href="mailto:haskell@fvisser.nl">haskell@fvisser.nl</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
Hi all,<br>
<br>
The STM monad currently has no MonadFix instance, but wonderful things are possible when it has one.<br>
<br>
I propose adding the &#39;MonadFix STM&#39; instance provided by Antoine Latter on the Haskell-Cafe[1] list to the STM package:<br>
<br>
&gt; {-# LANGUAGE MagicHash, UnboxedTuples, DoRec #-}<br>
&gt;<br>
&gt; import GHC.Exts<br>
&gt; import GHC.Conc<br>
&gt; import Control.Monad.Fix<br>
&gt;<br>
&gt; data STMret a = STMret (State# RealWorld) a<br>
&gt;<br>
&gt; liftSTM :: STM a -&gt; State# RealWorld -&gt; STMret a<br>
&gt; liftSTM (STM m) = \s -&gt; case m s of (# s&#39;, r #) -&gt; STMret s&#39; r<br>
&gt;<br>
&gt; instance MonadFix STM where<br>
&gt;   mfix k = STM $ \s -&gt;<br>
&gt;     let ans        = liftSTM (k r) s<br>
&gt;         STMret _ r = ans<br>
&gt;     in case ans of STMret s&#39; x -&gt; (# s&#39;, x #)<br>
<br>
Discussion Period: 1 week<br>
<br>
<br>
<br>
-Sebastiaan Visser<br>
<br>
[1] <a href="http://www.haskell.org/pipermail/haskell-cafe/2011-February/089226.html" target="_blank">http://www.haskell.org/pipermail/haskell-cafe/2011-February/089226.html</a><br>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org">Libraries@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/mailman/listinfo/libraries</a><br>
</blockquote></div><br></div>