[Haskell-cafe] broadcasting stateful computations
YueCompl
compl.yue at icloud.com
Thu Sep 2 08:45:48 UTC 2021
I believe this is the use case for TMVar, use `takeTMVar` / `putTMVar` instead of `readTVar` / `writeTVar` will do. And maybe `finally` `tryPutTMVar` back the original value you took out, in case sth went wrong before you can put an updated result back.
> On 2021-09-01, at 22:44, Olaf Klinke <olf at aatal-apotheke.de> wrote:
>
> Dear Café,
>
> I have a sequence of state-modifying computations
>
> action :: MonadUnliftIO m => StateT s m ()
>
> where the state s should be visible to other threads. Thus I created a
> TVar in which I keep track of this state s for other threads to read.
>
> The type system tells me it can't be done, which suggests I am using
> the wrong abstraction. The following type-checks but may be unsafe.
>
> import Control.Concurrent.STM
> import Control.Monad.IO.Unlift
> updateStateTVar :: MonadUnliftIO m => TVar s -> StateT s m () -> m ()
> updateStateTVar var action = withRunInIO (\inIO -> do
> s0 <- atomically (readTVar var)
> s1 <- inIO (execStateT action s0)
> atomically (writeTVar var s1))
>
> Yet the splitting into readTVar and writeTVar is dangerous if several
> threads have read/write access to the same TVar. I was hoping to write
> the above using modifyTVar. However, the action essentially gives me a
> Kleisli map
> s -> m s
> which I somehow have to turn into an
> m (s -> s)
> but it is not possible in general. (The reverse works for any functor.)
>
> What should I do?
> * Switch to WriterT (Endo s) m?
> This is not as powerful as StateT s m.
> * Do everything in the STM monad? But this disallows arbitrary IO
> because it would facilitate nested STM transactions.
>
> The code above is safe, I believe, if only one thread has read/write
> access and the others are read-only. Are there type-level abstractions
> of this kind? (I suppose one could easily make them with some
> newtypes.)
>
> Thanks in advance for any thoughts on this.
> Olaf
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
More information about the Haskell-Cafe
mailing list