[Haskell-cafe] broadcasting stateful computations

Isaac Elliott isaace71295 at gmail.com
Thu Sep 2 22:29:52 UTC 2021


How about using a read-write lock?

data Locked a = Locked { lockVar :: TVar Bool, valueVar :: TVar a }

new :: a -> IO (Locked a)
new val = Locked <$> newTVarIO False <*> newTVarIO val

-- lock blocks until unlocked
lock, unlock :: Locked a -> STM ()

-- never blocks
read :: Locked a -> STM a

-- blocks until unlocked
write :: Locked a -> a -> STM ()

When you want to apply your effectful state trasition `f :: s -> m s`:

l <- ask
s <- liftIO . atomically $ lock l *> read l
s' <- f s
liftIO . atomically $ write l s' *> unlock l

On Fri, 3 Sep 2021, 3:46 am Olaf Klinke, <olf at aatal-apotheke.de> wrote:

> On Fri, 2021-09-03 at 00:00 +0800, YueCompl wrote:
> > Um, I'm not sure I understand your case right, but if the "mutation"
> instead of the "mutated result" can be (might non-trivially) computed from
> a possibly outdated state, and the "mutation" can be trivially applied, I
> think `modifyTVar'` is the way to go. `readTVar` can be used to obtain an
> almost up-to-date state on demand, at low frequency.
>
> To be concrete, my state is a collection of time stamped values, where
> the monoid operation overwrites old values with new ones.
> But I need to know the current state (x,t) to determine the "mutation",
> because I'll be asking questions like "server, tell me if there is a
> value of x newer than t."
> Any observer whose initial state is synchronized with the worker thread
> can in principle re-construct the worker's internal state by observing
> the stream of emitted "mutations".
>
> The most general abstraction would be that of a monoid action on a
> type, but in my case the monoid (mutations) and the mutated type are
> identical.
>
> act :: m -> a -> a
> act memtpy = id
> act (x <> y) = act x . act y -- monoid homomorphism
> act (x <> x) = act x         -- idempotent
>
> 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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210903/50aa1d5d/attachment.html>


More information about the Haskell-Cafe mailing list