[Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

Ryan Ingram ryani.spam at gmail.com
Wed Apr 23 15:07:06 EDT 2008


On 4/23/08, apfelmus <apfelmus at quantentunnel.de> wrote:
> I don't quite understand what you want to do but I presume it's related to
> the following: given an expression like
>
>   readTVar intV >>= (\ -> ... readTVar boolV >>= (\_ -> ... retry))
>
> The ... indicate branches that are there have not been taken in our example
> run, so the STM-side-effects that have been performed are
>
>   readTVar intV
>   readTVar boolV
>   retry
>
> The thread waits for either  intV  or  boolV  to change. Now, assume that
> boolV  changes. Then, the idea for improving performance is to not restart
> the whole transaction, but only the part after the  readTVar boolV . In
> other words, only the continuation (\_ -> ... retry) will be executed again
> (and possibly yield something different from  retry ). I'm not sure whether
> this is currently implemented in Control.STM.

This isn't exactly correct, no.  The idea was to attach an additional
predicate to readTVar in the STM log, so that we know the result
cannot affect the computation as long as the predicate is unchanged.

> It seems that your scheme wants even more. You want to avoid work when intV
> changes, because the predicate for  boolV  clearly indicates that no matter
> what  intV  is, we'll have to retry anyway. Unfortunately, I don't think it
> works: the predicate itself might depend on  intV
>
>  interesting = atomically $
>    readTVar intV >>= $ \i ->
>    if i > 50 then retry else
>       retryUntil boolV (even i ==)
>
> That's the general property of  >>= , you always have to evaluate its right
> argument when the left argument changes. In essence, we have the same
> problem with parser combinators. Applicative functors to the rescue!

Ah, but that's the exact thing that retryUntil prevents; retryUntil
doesn't return the value of the variable read; it has exactly two
options:

retryUntil v p ~= do
   x <- readTVar v
   if (p x) then return () else retry

Now, a simple implementation would re-run the computation after each
change to v.  But we can take advantage of the knowledge that
retryUntil imparts no knowledge to the rest of the computation besides
"this predicate succeeded on the contents of this tvar", to make the
transaction log smarter.

So, in the case of "interesting", the transaction log would look
something like this:

retryUntil intV (> 50) => True
retryUntil boolV id => False
retry

Now, lets say intV changes from 100 to 101; we can look at this
transaction log, re-test the predicate (> 50), notice that the log
itself remains unchanged, and leave the transaction suspended without
worrying that the remainder of the computation was affected.

Using Tim Harris' proposed "readTVarWhen" combinator, this guarantee
is weakened; although the rule does hold for reads that fail the
predicate:

interesting2 = atomically $ do
    x <- readTVarWhen intV (>50)
    readTVarWhen intV2 (x ==)

readTVarWhen intV (>50) => True
readTVarWhen intV2 (x ==) => False
retry

If intV2 changes but the predicate stays false, we don't have to
re-run the computation, but if intV changes we absolutely do.  This is
made clear by my definition of readTVarWhen:

readTVarWhen v p = retryUntil v p >> readTVar v

In this case the transaction log would look like this:

retryUntil intV (>50) => True
readTVar intV
retryUntil intV2 (== x) => False
retry

Now if intV changes it's clear in the transaction log that the
transaction needs to be re-run.

  -- ryan


More information about the Haskell-Cafe mailing list