[Haskell-cafe] broadcasting stateful computations

Olaf Klinke olf at aatal-apotheke.de
Thu Sep 2 15:25:12 UTC 2021


Thanks everyone for the helpful suggestions!

Bryan Richer wrote:
> what if the TVar is part of the
> state s?
> (StateT IO) can't give any guarantees about when or how the state is
> broadcast, but using STM within StateT actions still can.

I don't understand this, but it may go into the same direction as:

Chris Smith wrote:
> I had the same suggestion.  However, you then no longer need StateT, as
> ReaderT is enough.  Using a `ReaderT (TVar s) IO a` will allow atomic
> changes to the state s, along with interleaved IO when it's done safely
> rather than in the middle of a transaction.

ReaderT (TVar s) IO is interesting! It does not solve the problem of
atomic modifications with side-effects, though. Currently I am
implicity using ReaderT (TVar s), by explicitly passing the TVar
around. 

In principle, for atomic modifications I have to get hold of a pure
version (s -> s) of the modification. Maybe within a monadic context.
But if determining this modification function is side-effectful, then
it can not depend on the initial contents of the TVar! 

This leads me to the conclusion that either 
(a) atomic modification by a Kleisli map is impossible and another
mechanism needs to ensure thread safety, or
(b) we need to keep two versions of the state: one private, pure s and
one public TVar s which we synchronize from time to time. The latter
can be accomplished with atomic writes. More on that below.  

Isaac Elliott wrote:
> What about creating a MonadState instance for the TVar?
Very neat, but it would not solve the atomicity problem, since the
update I have is not expressible as stateTVar. 

YueCompl wrote:
> I believe this is the use case for TMVar, use `takeTMVar` / `putTMVar` instead of `readTVar` / `writeTVar` will do.

TMVars appear non-empty for one thread only, as far as I understand. 
So any observer thread would be blocked while the worker thread is
updating the state? 
Not good for my use case. The observer thread will be a webserver. 
I'd rather have the webserver report old states than block. 

I have neglected to mention one aspect of my problem that might be
essential: All my state updates are monoidal. By that I mean that s is
a monoid with 
	s' <> s <> s = s' <> s 
and any effectful modification will be of the form 
f = \s -> (k s) >>= (\s' -> s' <> s)
for some k :: s -> m s.
This entails that instead of emitting modifications as functions I can
emit modifications as values. 

emitModification :: (Monad m, Monoid s) => 
  StateT s m a -> WriterT s (StateT s m) a
emitModification (StateT f) = WriterT $ StateT $ \s -> do 
   (a,s') <- f s 
   return ((a,s'),s')

broadcastModification :: (MonadIO m, Semigroup s) => 
  TVar s -> (WriterT s m) a -> m a
broadcastModification ref (WriterT m) = do 
   (a,s') <- m
   (liftIO.atomically) (modifyTVar ref (\s -> s' <> s))
   return a

Then 
\ref -> broadcastModification ref . emitModification
  :: (MonadIO m, Monoid s) => 
    TVar s -> StateT s m a -> StateT s m a

This has the additional charm that I can explicitly control when writes
to the TVar happen, by choosing which (StateT s m) blocks to enclose in
this wrapper. I might even set up my communication as a TChan, if the
observing thread maintains an own copy of state itself to merge the
updates s' into. 

Olaf



More information about the Haskell-Cafe mailing list