broadcasting stateful computations

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

You've maybe already considered this, but 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.
On Wed, 1 Sep 2021, 17.45 Olaf Klinke,
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.

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. On Wed, Sep 1, 2021 at 11:17 AM Bryan Richter wrote:
You've maybe already considered this, but 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.
On Wed, 1 Sep 2021, 17.45 Olaf Klinke,
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.
_______________________________________________ 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.

What about creating a MonadState instance for the TVar?
newtype SharedStateT m a = SharedStateT (ReaderT (TVar s) m a)
instance MonadIO m => MonadState s (SharedStateT s m) where
get = SharedStateT $ liftIO . readTVarIO =<< ask
put s = SharedStateT $ do
tvar <- ask
liftIO . atomically $ writeTVar tvar s
state f = SharedStateT $ do
tvar <- ask
liftIO . atomically $ stateTVar tvar f
On Thu, 2 Sep 2021, 12:50 am Olaf Klinke,
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.

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
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.
participants (5)
-
Bryan Richter
-
Chris Smith
-
Isaac Elliott
-
Olaf Klinke
-
YueCompl