Relaxing atomicity of STM transactions

Has anyone in the STM community considered the ability to read a TVar, such that it would allow the transaction to complete even if the TVar was modified by another transaction? (I am assuming this is not how STM works by default.) For example: looselyReadTVar :: TVar a -> STM a Atom [1] has similar semantics to STM. If Atom were to relax it's rule atomicity in this fashion, it could open the door to improved task scheduling and higher levels of program description. Has STM research already gone down this path? -Tom [1] http://hackage.haskell.org/package/atom

On 28 September 2010 15:35, Tom Hawkins
Has anyone in the STM community considered the ability to read a TVar, such that it would allow the transaction to complete even if the TVar was modified by another transaction?
Maybe something like this: (Pasted from http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/GHC-Conc.... ) readTVarIO :: TVar a -> IO a Return the current value stored in a TVar. This is equivalent to readTVarIO = atomically . readTVar but works much faster, because it doesn't perform a complete transaction, it just reads the current value of the TVar. Peter
(I am assuming this is not how STM works by default.) For example:
looselyReadTVar :: TVar a -> STM a
Atom [1] has similar semantics to STM. If Atom were to relax it's rule atomicity in this fashion, it could open the door to improved task scheduling and higher levels of program description. Has STM research already gone down this path?
-Tom
[1] http://hackage.haskell.org/package/atom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Sep 28, 2010 at 10:41 AM, Peter Robinson
readTVarIO :: TVar a -> IO a
One needs to know if it is ok to wrap this IO action into an STM action. For example,
data I a = I a
looselyReadTVar :: TVar a -> STM a looselyReadTVar tvar = let v = unsafePerformIO (I <$> readTVarIO tvar) in case v of I x -> return x
The 'case' is needed because otherwise the TVar would be read only when its value was requested, and we want to keep the ordering. The 'I' datatype is used to avoid evaluating the user's value (which could even be 'undefined'). Note that this function can be used on any monad, but I don't think that is a good idea =). Cheers! -- Felipe.

On Tue, Sep 28, 2010 at 8:54 AM, Felipe Lessa
On Tue, Sep 28, 2010 at 10:41 AM, Peter Robinson
wrote: readTVarIO :: TVar a -> IO a
One needs to know if it is ok to wrap this IO action into an STM action. For example,
data I a = I a
looselyReadTVar :: TVar a -> STM a looselyReadTVar tvar = let v = unsafePerformIO (I <$> readTVarIO tvar) in case v of I x -> return x
The 'case' is needed because otherwise the TVar would be read only when its value was requested, and we want to keep the ordering. The 'I' datatype is used to avoid evaluating the user's value (which could even be 'undefined').
Note that this function can be used on any monad, but I don't think that is a good idea =).
Cheers!
Isn't there an 'unsafeIOToSTM' function somewhere? Something like:
unsafeIOToSTM (IO k) = STM k
Then you might not need the case statement. Antoine

On Tue, Sep 28, 2010 at 11:01 AM, Antoine Latter
Isn't there an 'unsafeIOToSTM' function somewhere? Something like:
unsafeIOToSTM (IO k) = STM k
Then you might not need the case statement.
I thought there was, but I couldn't find it in the 'stm' package [1], using Hoogle [2] nor using Hayoo [3]. [1] http://hackage.haskell.org/package/stm [2] http://haskell.org/hoogle/?hoogle=IO+a+-%3E+STM+a [3] http://holumbus.fh-wedel.de/hayoo/hayoo.html#0:stmtoio -- Felipe.

On Tue, Sep 28, 2010 at 9:05 AM, Felipe Lessa
On Tue, Sep 28, 2010 at 11:01 AM, Antoine Latter
wrote: Isn't there an 'unsafeIOToSTM' function somewhere? Something like:
unsafeIOToSTM (IO k) = STM k
Then you might not need the case statement.
I thought there was, but I couldn't find it in the 'stm' package [1], using Hoogle [2] nor using Hayoo [3].
Funny - I had the module open in another window as I wrote my response. It's in GHC.Conc[1]:
unsafeIOToSTM :: IO a -> STM a
defined as I had guessed. Antoine [1] http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/GHC-Conc....

Thanks for the responses, but I think I should explain a bit more. I'm not interested in being able to read the live value of a TVar at any arbitrary time (via. unsafeIOToSTM). But rather I would like looslyReadTVar to have exactly the same semantics as readTVar, except that the STM runtime would not reject the transaction if the TVar is modified by another transaction before the atomic commit takes place. Also, as I would be implementing something similar in Atom, I'm not necessarily interested in a Haskell implementation, but rather if the programming experience is elevated by these alternative semantics. For example: incr :: TVar -> STM () incr a = looslyReadTVar a >>= writeTVar a . (+ 1) decr a :: TVar -> STM () decr a = readTVar a >>= writeTVar a . (- 1) If incr and decr where atomically started at the same time with the same TVar, decr would be rejected if incr completed first, but not the other way around. The initial reaction may be that this seriously breaks the atomicity of STM, but there may be cases where this could be useful. For instance, it allow a computationally expensive transactions to complete, even if their inputs are constantly being modified. In the embedded domain, this could be a fault monitor that reads a bunch of constantly changing sensors. -Tom

On Tue, Sep 28, 2010 at 6:44 PM, Serguey Zefirov
2010/9/29 Tom Hawkins
: In the embedded domain, this could be a fault monitor that reads a bunch of constantly changing sensors.
I think that sensor reading belongs to IO, not STM.
Sensors would be transfered from IO to TVars via a transaction in an input processing thread. My question is not this, but is looselyReadTVar advantageous to STM programming in general? My applications can't use Haskell STM, nor the Haskell runtime, due to their hard realtime requirements. -Tom

Clojure has a commute operator whose semantics seem appropriate to your concerns: http://clojure.org/refs http://richhickey.github.com/clojure/clojure.core-api.html#clojure.core/comm... Commute in haskell would be roughly :: TVar a -> (a -> a) -> STM a. The TVar touched by commute does not get marked such that the transaction could retry. Nor is the TVar itself even updated at the time. Rather, it is read, and the result of applying some transform to it is returned. Then, when the transaction commits, the tvar is atomically modified by the function and actually updated. This works if the operation commutes with all other operations performed on the TVar anywhere else that may be running concurrently, and if no essential use (i.e. requiring atomicity) is made of the value returned from commute. Both properties can only be enforced by the discipline of the programmer. I don't know how much discussion there's been in the Clojure community about the utility of commute, as a quick google mainly reveals people trying to either figure it out or explain it. Cheers, Sterl. On Sep 28, 2010, at 7:36 PM, Tom Hawkins wrote:
Thanks for the responses, but I think I should explain a bit more. I'm not interested in being able to read the live value of a TVar at any arbitrary time (via. unsafeIOToSTM). But rather I would like looslyReadTVar to have exactly the same semantics as readTVar, except that the STM runtime would not reject the transaction if the TVar is modified by another transaction before the atomic commit takes place.
Also, as I would be implementing something similar in Atom, I'm not necessarily interested in a Haskell implementation, but rather if the programming experience is elevated by these alternative semantics.
For example:
incr :: TVar -> STM () incr a = looslyReadTVar a >>= writeTVar a . (+ 1)
decr a :: TVar -> STM () decr a = readTVar a >>= writeTVar a . (- 1)
If incr and decr where atomically started at the same time with the same TVar, decr would be rejected if incr completed first, but not the other way around. The initial reaction may be that this seriously breaks the atomicity of STM, but there may be cases where this could be useful. For instance, it allow a computationally expensive transactions to complete, even if their inputs are constantly being modified. In the embedded domain, this could be a fault monitor that reads a bunch of constantly changing sensors.
-Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Tom, you can do this with Twilight STM. I recently uploaded the first version on hackage[1]. The next version including a better algorithm and examples is about to be released in a few days. Twilight STM features include tagging of variables and fine-grained conflict detection, flexible isolation level semantics (snapshot isolation and opacity) as well as safe integration of I/O. - Annette [1] http://hackage.haskell.org/package/twilight-stm Am 28.09.2010 15:35, schrieb Tom Hawkins:
Has anyone in the STM community considered the ability to read a TVar, such that it would allow the transaction to complete even if the TVar was modified by another transaction? (I am assuming this is not how STM works by default.) For example:
looselyReadTVar :: TVar a -> STM a
Atom [1] has similar semantics to STM. If Atom were to relax it's rule atomicity in this fashion, it could open the door to improved task scheduling and higher levels of program description. Has STM research already gone down this path?
-Tom
[1] http://hackage.haskell.org/package/atom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Antoine Latter
-
bieniusa
-
Felipe Lessa
-
Peter Robinson
-
Serguey Zefirov
-
Sterling Clover
-
Tom Hawkins