<html><head></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; "><div><div><div>On Feb 17, 2011, at 3:24 PM, Edward Kmett wrote:</div><blockquote type="cite">+1, but to quibble, even for trivial things like this we usually try to allow at least 2 weeks for discussion.</blockquote><div><br></div><div>No problem, 2 weeks is fine with me.</div><br><blockquote type="cite"><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'm not biased one way or the other.</div></blockquote><div><br></div><div>I hope STM maintainers have an opinion on this one, I couldn't really tell.</div><br><blockquote type="cite"><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-top: 0px; margin-right: 0px; margin-bottom: 0px; margin-left: 0.8ex; border-left-width: 1px; border-left-color: rgb(204, 204, 204); border-left-style: solid; padding-left: 1ex; position: static; z-index: auto; ">
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 'MonadFix STM' 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', r #) -&gt; STMret s' r<br>
&gt;<br>
&gt; instance MonadFix STM where<br>
&gt; &nbsp; mfix k = STM $ \s -&gt;<br>
&gt; &nbsp; &nbsp; let ans &nbsp; &nbsp; &nbsp; &nbsp;= liftSTM (k r) s<br>
&gt; &nbsp; &nbsp; &nbsp; &nbsp; STMret _ r = ans<br>
&gt; &nbsp; &nbsp; in case ans of STMret s' x -&gt; (# s', 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></blockquote></div></div></blockquote></div><br></div></body></html>