[Haskell-cafe] Combining ST with STM

Thomas Koster tkoster at gmail.com
Tue Feb 9 12:46:36 UTC 2016


On 9 February 2016 at 14:43, Thomas Koster <tkoster at gmail.com> wrote:
> I have an STM transaction that needs some private, temporary state.
> The most obvious way is to simply pass pure state as arguments, but
> for efficiency, I would like this state to be some kind of mutable
> array, like STArray.
>
> The private state is, by definition, not shared, so
> including it in the STM log and commit process is, as far as I can
> tell, pointless.
>
> ST and STArray still appear to be the most appropriate tools for the
> private state, because STRefs and STArrays really, really are private.
>
> So this basically means I want to interleave ST and STM in a "safe"
> way. That is, if the STM transaction retries, I want the ST state to
> be vaporised as well.
>
> Ideally, I would love to be able to say something like this:
>
> -- | Copy the value from the shared TVar into the private STRef.
> load :: TVar a -> STRef a -> STSTM s ()
> load shared private = do
>   value <- liftSTM (readTVar shared)
>   liftST (writeSTRef private value)
>
> Naturally, that STRef must originate from a call to newSTRef earlier
> in the same transaction and is private to it, just like the real ST
> monad. As far as I can tell, I am not trying to weaken either ST or
> STM in any way here.

Please forgive the typo in the type signature of "load", which should
have been:

load :: TVar a -> STRef s a -> STSTM s ()

Let me elaborate on STSTM, a monad I made up for this example that
combines the characteristics of ST and STM in the way that I want.
If my requirements were unclear from my prose, perhaps the code below
will illuminate them better.

An STSTM transaction is intended to be an STM transaction imbued with a
state token that encapsulates additional, transaction-local state in the
spirit of ST.

It is not intended to secretly perform IO inside STM, a la
GHC.Conc.unsafeIOToSTM.

It is not intended to facilitate the leaking of state into or out of an
STM transaction through STRefs, nor to communicate state between
successive retries of an STM transaction.

Thanks to hints from Ryan and Jonas, I made an attempt at implementing
it myself.

Below is my implementation of STSTM and associated operations. You will
need to link with the "primitive" and "stm" packages. I used versions
0.6 and 2.4.4, resp., and GHC 7.10.2.


{-# LANGUAGE GeneralizedNewtypeDeriving, Rank2Types #-}

module Control.Monad.STSTM
  (
    STSTM,
    liftST,
    liftSTM,
    atomicallyRunST,
    module Control.Monad.STM
  )
where

import Control.Monad.Primitive
import Control.Monad.ST
import Control.Monad.STM

-- | A computation of type @STSTM s a@ is an 'STM' computation that
-- also transforms a transaction-local internal state indexed by @s@, as
-- in the 'ST' monad, and returns a value of type @a at .
newtype STSTM s a = STSTM { unSTSTM :: STM a }
  deriving (Functor, Applicative, Monad)

-- | Lift an 'ST' computation into the 'STSTM' transaction.
liftST :: ST s a -> STSTM s a
{-# INLINE liftST #-}
liftST x = STSTM $
  let y = unsafeInlineST x
  in  y `seq` return y

-- | Lift an 'STM' computation into the 'STSTM' transaction.
liftSTM :: STM a -> STSTM s a
{-# INLINE liftSTM #-}
liftSTM = STSTM

-- | Perform a series of 'STSTM' actions atomically.
--
-- The 'ST' state is discarded when the 'STM' transaction commits or
-- retries.
atomicallyRunST :: (forall s. STSTM s a) -> IO a
{-# INLINE atomicallyRunST #-}
atomicallyRunST x = atomically (unSTSTM x)


Some commentary follows:

Some initial sanity testing with the GHC threaded runtime shows that it
does what I want, but I am not familiar enough with Core or the RTS to
predict whether or not it will launch nuclear missiles at the next
transit of Venus. I would be grateful for any feedback.

The use of rank-2 polymorphism in the type of atomicallyRunST is
intended to encapsulate the ST state exactly like it does for runST,
and that the ST state cannot leak into or out of the transaction.

STSTM is not a monad transformer (visibly or internally). I hope that
any potential problems that might afflict the STMonadTrans package are
irrelevant here.

I use seq in liftST to force the unsafe inline ST computation to occur
before bind proceeds to the next computation. Without seq, ST
computations returning () (or anything else that is not evaluated)
appear to stay as thunks and never transform any state. I suspect this
may cause problems with bottoms, but I am not sure if that is any
different from real ST/runST.

--
Thomas Koster


More information about the Haskell-Cafe mailing list