Proposal: Add MonadFix instance to STM

Edward Kmett ekmett at gmail.com
Thu Feb 17 15:24:21 CET 2011


+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 <haskell at fvisser.nl>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
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110217/fb408d8d/attachment.htm>


More information about the Libraries mailing list