Proposal: Add MonadFix instance to STM

Sebastiaan Visser haskell at fvisser.nl
Thu Feb 17 14:57:08 CET 2011


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


More information about the Libraries mailing list