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

Matthew Brecknell haskell at brecknell.org
Wed Apr 23 22:13:15 EDT 2008


Ryan Ingram said:
> So, if have a transaction T that is waiting inside "retry" for a
> variable that it read to change, and a variable that is only accessed
> in a "subatomic" part of T is changed, we can try running the
> subatomic computation first.  Here are the four cases:
> 
> 1) The subatomic computation succeeded before and still succeeded.
> Then we know the end result of the computation is unaffected, and will
> still retry.  No need to do anything.
> 2) The subatomic computation succeeded before and now fails (calls
> 'retry' or retryRO').  Then we know that the computation will now fail
> at this earlier point.  Mark the change to "fail" in the transaction
> log and leave the computation in the "waiting for retry" state.
> 3) The subatomic computation failed before and still fails.  See (1)
> 4) The subatomic computation failed before and now succeeds.  The
> result of the entire computation can change, we should now re-run the
> entire computation.

I'm trying to figure out whether subatomic could be weakened to allow
writes as well as reads. I don't think this change would affect cases 2
to 4 above. But in case 1, the subatomic computation might perform a
different set of writes, which might affect the outcome of the outer
computation, so it is not safe to continue blocking. It's case 1 which
makes retryUntil (and subatomic) stronger than readTVarWhen.

If it's not possible to weaken subatomic to allow writes, without
affecting case 1, then I think this also means that subatomic/retryUntil
is stronger than the hypothetical "continuation-logging" implementation
previously hinted at by David, apfelmus and myself (that is, one which
treats each individual read as a kind of checkpoint, by recording the
read's continuation in the transaction log, and using that continuation
to restart the blocked transaction).

Nevertheless, the distinction between read-only and read-write
transactions does not necessarily have to occur at the level of types.
STM is fundamentally a dynamic approach to concurrency control, so I
think it would make sense for transactions to *dynamically* determine
whether they are read-only or read-write, as they compose with each
other.

In that case, we can treat subatomic as a "hint" to the STM runtime. It
could have a simpler type, and the semantics of "id":

subatomic :: STM a -> STM a

If the subatomic transaction turns out to be read-only, then we get the
benefit of all four cases Ryan describes above. If it turns out to be
read-write, we only get the benefit of cases 2 to 4, while case 1 must
restart. It doesn't matter if the subatomic transaction captures
variables which depend on previous reads, since changes to those reads
would cause a restart regardless of the outcome of the subatomic
transaction.

Moreover, note that the hypothetical "continuation-logging"
implementation could implement (m >>= k) by implicitly wrapping every m
in a call to subatomic. Of course, that would require a lot of
speculative book-keeping. I think this means that subatomic is not a
fundamental abstraction, but could be a useful pragmatic optimisation.



More information about the Haskell-Cafe mailing list