Proposal: Add MonadFix instance to STM

Hi all, The STM monad currently has no MonadFix instance, but wonderful things are possible when it has one. I propose adding the 'MonadFix STM' instance provided by Antoine Latter on the Haskell-Cafe[1] list to the STM package:
{-# LANGUAGE MagicHash, UnboxedTuples, DoRec #-}
import GHC.Exts import GHC.Conc import Control.Monad.Fix
data STMret a = STMret (State# RealWorld) a
liftSTM :: STM a -> State# RealWorld -> STMret a liftSTM (STM m) = \s -> case m s of (# s', r #) -> STMret s' r
instance MonadFix STM where mfix k = STM $ \s -> let ans = liftSTM (k r) s STMret _ r = ans in case ans of STMret s' x -> (# s', x #)
Discussion Period: 1 week -Sebastiaan Visser [1] http://www.haskell.org/pipermail/haskell-cafe/2011-February/089226.html

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

On Feb 17, 2011, at 3:24 PM, Edward Kmett wrote:
+1, but to quibble, even for trivial things like this we usually try to allow at least 2 weeks for discussion.
No problem, 2 weeks is fine with me.
Why not just import STRet from GHC.ST and exploit that rather than redefine it? Just curious -- I'm not biased one way or the other.
I hope STM maintainers have an opinion on this one, I couldn't really tell.
-Edward
On Thu, Feb 17, 2011 at 8:57 AM, Sebastiaan Visser
wrote: Hi all, The STM monad currently has no MonadFix instance, but wonderful things are possible when it has one.
I propose adding the 'MonadFix STM' instance provided by Antoine Latter on the Haskell-Cafe[1] list to the STM package:
{-# LANGUAGE MagicHash, UnboxedTuples, DoRec #-}
import GHC.Exts import GHC.Conc import Control.Monad.Fix
data STMret a = STMret (State# RealWorld) a
liftSTM :: STM a -> State# RealWorld -> STMret a liftSTM (STM m) = \s -> case m s of (# s', r #) -> STMret s' r
instance MonadFix STM where mfix k = STM $ \s -> let ans = liftSTM (k r) s STMret _ r = ans in case ans of STMret s' x -> (# s', x #)
Discussion Period: 1 week
-Sebastiaan Visser
[1] http://www.haskell.org/pipermail/haskell-cafe/2011-February/089226.html
participants (2)
-
Edward Kmett
-
Sebastiaan Visser