SimonPJ and Tim Harris explain STM - video

http://channel9.msdn.com/Showpost.aspx?postid=231495 The links to the video are a couple of yellow buttons at the bottom of the article: "Watch" or "Download". I haven't watched this yet (it's nearly an hour long, I think). Found via reddit (http://reddit.com). Haskeller's on TV (sort of...) woot woot! Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

A comment on that video said:
----- BEGIN QUOTE ----
It seems to me that STM creates new problems with composability.
You create two classes of code: atomic methods and non atomic methods.
Nonatomic methods can easily call atomic ones – the compiler could
even automatically inject the atomic block if the programmer forgot.
Atomic methods and blocks cannot be allowed to call nonatomic code.
The nonatomic code could do I/O or other irrevocable things that would
be duplicated when the block had to retry.
---- END QUOTE ----
I imagine an example like this (some pseudo code for a side effect
happy OO language):
class Foo {
protected int counter; // assume this gets initialized to 0
public doSomething() {
atomic{
counter++;
Console.Write("called doSomething execution# " + counter);
// something which could cause the transaction to restart
}
}
public doOtherThing() {
atomic{
doSomething();
// something which could cause the transaction to restart
}
}
}
Now imagine doSomething gets restarted, then we see the console output
once each time and counter gets incremented. So one solution would be
to move the side effects (counter++ and the console write) to happen
before the atomic block. This works for doSomething, but now what if
we called doOtherThing instead? We're back to having the extra
side-effects from the failed attempts at doSomething, right? We just
lost composability of doSomething? I'm assuming counter is only meant
to be incremented once per successful run of doSomething and we only
want to see the output to the log file once per successful run, but it
needs to come before the log output inside doSomething so that the log
makes sense.
I realize STM is not a silver bullet, but it does seem like
side-effects do not play nicely with STM. What is the proposed
solution to this? Am I just missing something simple? Is the
solution to make it so that Console.Write can be rolled back too?
Thanks,
Jason
On 11/23/06, Bayley, Alistair
http://channel9.msdn.com/Showpost.aspx?postid=231495
The links to the video are a couple of yellow buttons at the bottom of the article: "Watch" or "Download".
I haven't watched this yet (it's nearly an hour long, I think). Found via reddit (http://reddit.com).
Haskeller's on TV (sort of...) woot woot!
Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. ***************************************************************** _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 23/11/06, Jason Dagit
A comment on that video said:
----- BEGIN QUOTE ---- It seems to me that STM creates new problems with composability. You create two classes of code: atomic methods and non atomic methods.
Nonatomic methods can easily call atomic ones – the compiler could even automatically inject the atomic block if the programmer forgot.
Atomic methods and blocks cannot be allowed to call nonatomic code. The nonatomic code could do I/O or other irrevocable things that would be duplicated when the block had to retry. ---- END QUOTE ----
I imagine an example like this (some pseudo code for a side effect happy OO language):
class Foo { protected int counter; // assume this gets initialized to 0 public doSomething() { atomic{ counter++; Console.Write("called doSomething execution# " + counter); // something which could cause the transaction to restart } } public doOtherThing() { atomic{ doSomething(); // something which could cause the transaction to restart } } }
Now imagine doSomething gets restarted, then we see the console output once each time and counter gets incremented. So one solution would be to move the side effects (counter++ and the console write) to happen before the atomic block. This works for doSomething, but now what if we called doOtherThing instead? We're back to having the extra side-effects from the failed attempts at doSomething, right? We just lost composability of doSomething? I'm assuming counter is only meant to be incremented once per successful run of doSomething and we only want to see the output to the log file once per successful run, but it needs to come before the log output inside doSomething so that the log makes sense.
I realize STM is not a silver bullet, but it does seem like side-effects do not play nicely with STM. What is the proposed solution to this? Am I just missing something simple? Is the solution to make it so that Console.Write can be rolled back too?
Thanks, Jason
The solution is to simply not allow side effecting computations in transactions. They talk a little about it in the video, but perhaps that's not clear. The only side effects an atomic STM transaction may have are changes to shared memory. Another example in pseudocode: atomic x <- launchMissiles if (x < 5) then retry This is obviously catastrophic. If launchMissiles has the side effect of launching a salvo of missiles, and then the retry occurs, it's unlikely that rolling back the transaction is going to be able to put them back on the launchpad. Worse yet, if some variable read in launchMissiles changes, the transaction would retry, possibly causing a second salvo of missiles to be launched. So you simply disallow this. The content of a transaction may only include reads and writes to shared memory, along with pure computations. This is especially easy in Haskell, because one simply uses a new monad STM, with no way to lift IO actions into that monad, but atomically :: (STM a -> IO a) goes in the other direction, turning a transaction into IO. In other languages, you'd want to add some static typechecking to ensure that this constraint was enforced. - Cale

[sorry for quoting so much, kinda hard to decide here where to snip] Cale Gibbard wrote:
On 23/11/06, Jason Dagit
wrote: A comment on that video said:
----- BEGIN QUOTE ---- It seems to me that STM creates new problems with composability. You create two classes of code: atomic methods and non atomic methods.
Nonatomic methods can easily call atomic ones ? the compiler could even automatically inject the atomic block if the programmer forgot.
Atomic methods and blocks cannot be allowed to call nonatomic code. The nonatomic code could do I/O or other irrevocable things that would be duplicated when the block had to retry. ---- END QUOTE ----
I imagine an example like this (some pseudo code for a side effect happy OO language):
class Foo { protected int counter; // assume this gets initialized to 0 public doSomething() { atomic{ counter++; Console.Write("called doSomething execution# " + counter); // something which could cause the transaction to restart } } public doOtherThing() { atomic{ doSomething(); // something which could cause the transaction to restart } } }
Now imagine doSomething gets restarted, then we see the console output once each time and counter gets incremented. So one solution would be to move the side effects (counter++ and the console write) to happen before the atomic block. This works for doSomething, but now what if we called doOtherThing instead? We're back to having the extra side-effects from the failed attempts at doSomething, right? We just lost composability of doSomething? I'm assuming counter is only meant to be incremented once per successful run of doSomething and we only want to see the output to the log file once per successful run, but it needs to come before the log output inside doSomething so that the log makes sense.
I realize STM is not a silver bullet, but it does seem like side-effects do not play nicely with STM. What is the proposed solution to this? Am I just missing something simple? Is the solution to make it so that Console.Write can be rolled back too?
The solution is to simply not allow side effecting computations in transactions. They talk a little about it in the video, but perhaps that's not clear. The only side effects an atomic STM transaction may have are changes to shared memory.
Another example in pseudocode:
atomic x <- launchMissiles if (x < 5) then retry
This is obviously catastrophic. If launchMissiles has the side effect of launching a salvo of missiles, and then the retry occurs, it's unlikely that rolling back the transaction is going to be able to put them back on the launchpad. Worse yet, if some variable read in launchMissiles changes, the transaction would retry, possibly causing a second salvo of missiles to be launched.
So you simply disallow this. The content of a transaction may only include reads and writes to shared memory, along with pure computations. This is especially easy in Haskell, because one simply uses a new monad STM, with no way to lift IO actions into that monad, but atomically :: (STM a -> IO a) goes in the other direction, turning a transaction into IO. In other languages, you'd want to add some static typechecking to ensure that this constraint was enforced.
This is of course the technically correct answer. However, I suspect that it may not be completely satisfying to the practitioner. What if you want or even need your output to be atomically tied to a pure software transaction? One answer is in fact "to make it so that Console.Write can be rolled back too". To achieve this one can factor the actual output to another task and inside the transaction merely send the message to a transactional channel (TChan): atomic $ do increment counter counterval <- readvar counter sendMsg msgChan ("called doSomething execution# " ++ show counterval) -- something which could cause the transaction to restart Another task regularly takes messages from the channel and actually outputs them. Of course the output will be somewhat delayed, but the order of messages will be preserved between tasks sending to the same channel. And the message will only be sent if and only if the transaction commits. Unfortunately I can't see how to generalize this to input as well... Cheers Ben

(Dropping Haskell@hakell.org) Hi, We've not yet looked at I/O in detail in Haskell, but there's a paper from a few years back where I experimented with ways of integrating I/O with an earlier implementation of atomic blocks in Java. http://research.microsoft.com/~tharris/papers/2005-scp.pdf The basic idea is to provide a way for a transaction to call into transaction-aware libraries. The libraries can register callbacks for if the transaction commits (to actually do any "O") and for if the transaction aborts (to re-buffer any "I" that the transaction has consumed). In addition, a library providing access to another transactional abstraction (e.g. a database supporting transactions) can perform a 2-phase commit that means that the memory transaction and database transaction either both commit or both abort. Of course, these solutions don't deal with the question of atomic blocks that want to perform output (e.g. to the console) and receive input in response to that. My view at the moment is _that does not make sense in an atomic block_ -- the output and input can't be performed atomically because the intervening state must be visible for the user to respond to. We also briefly experimented with extending the SXM system Maurice Herlihy worked on at MSR Cambridge to support transactions that include accesses to the file system and registry -- http://msdn2.microsoft.com/en-us/library/aa366295.aspx describes the TxF and TxR systems it was built over. Some other interesting work in this area is Elliot Moss' papers on "open nested" transactions -- these provide another building block at the same level as the Java system I mentioned: library writers can use them with care to extend the range of things that can be done inside an atomic block. Cheers, Tim -----Original Message----- From: haskell-bounces@haskell.org [mailto:haskell-bounces@haskell.org] On Behalf Of Benjamin Franksen Sent: 24 November 2006 03:16 To: haskell@haskell.org Cc: haskell-cafe@haskell.org Subject: [Haskell] Re: [Haskell-cafe] SimonPJ and Tim Harris explain STM - video [sorry for quoting so much, kinda hard to decide here where to snip] Cale Gibbard wrote:
On 23/11/06, Jason Dagit
wrote: A comment on that video said:
----- BEGIN QUOTE ---- It seems to me that STM creates new problems with composability. You create two classes of code: atomic methods and non atomic methods.
Nonatomic methods can easily call atomic ones ? the compiler could even automatically inject the atomic block if the programmer forgot.
Atomic methods and blocks cannot be allowed to call nonatomic code. The nonatomic code could do I/O or other irrevocable things that would be duplicated when the block had to retry. ---- END QUOTE ----
I imagine an example like this (some pseudo code for a side effect happy OO language):
class Foo { protected int counter; // assume this gets initialized to 0 public doSomething() { atomic{ counter++; Console.Write("called doSomething execution# " + counter); // something which could cause the transaction to restart } } public doOtherThing() { atomic{ doSomething(); // something which could cause the transaction to restart } } }
Now imagine doSomething gets restarted, then we see the console output once each time and counter gets incremented. So one solution would be to move the side effects (counter++ and the console write) to happen before the atomic block. This works for doSomething, but now what if we called doOtherThing instead? We're back to having the extra side-effects from the failed attempts at doSomething, right? We just lost composability of doSomething? I'm assuming counter is only meant to be incremented once per successful run of doSomething and we only want to see the output to the log file once per successful run, but it needs to come before the log output inside doSomething so that the log makes sense.
I realize STM is not a silver bullet, but it does seem like side-effects do not play nicely with STM. What is the proposed solution to this? Am I just missing something simple? Is the solution to make it so that Console.Write can be rolled back too?
The solution is to simply not allow side effecting computations in transactions. They talk a little about it in the video, but perhaps that's not clear. The only side effects an atomic STM transaction may have are changes to shared memory.
Another example in pseudocode:
atomic x <- launchMissiles if (x < 5) then retry
This is obviously catastrophic. If launchMissiles has the side effect of launching a salvo of missiles, and then the retry occurs, it's unlikely that rolling back the transaction is going to be able to put them back on the launchpad. Worse yet, if some variable read in launchMissiles changes, the transaction would retry, possibly causing a second salvo of missiles to be launched.
So you simply disallow this. The content of a transaction may only include reads and writes to shared memory, along with pure computations. This is especially easy in Haskell, because one simply uses a new monad STM, with no way to lift IO actions into that monad, but atomically :: (STM a -> IO a) goes in the other direction, turning a transaction into IO. In other languages, you'd want to add some static typechecking to ensure that this constraint was enforced.
This is of course the technically correct answer. However, I suspect that it may not be completely satisfying to the practitioner. What if you want or even need your output to be atomically tied to a pure software transaction? One answer is in fact "to make it so that Console.Write can be rolled back too". To achieve this one can factor the actual output to another task and inside the transaction merely send the message to a transactional channel (TChan): atomic $ do increment counter counterval <- readvar counter sendMsg msgChan ("called doSomething execution# " ++ show counterval) -- something which could cause the transaction to restart Another task regularly takes messages from the channel and actually outputs them. Of course the output will be somewhat delayed, but the order of messages will be preserved between tasks sending to the same channel. And the message will only be sent if and only if the transaction commits. Unfortunately I can't see how to generalize this to input as well... Cheers Ben _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

| The basic idea is to provide a way for a transaction to call into transaction-aware libraries. The libraries | can register callbacks for if the transaction commits (to actually do any "O") and for if the transaction | aborts (to re-buffer any "I" that the transaction has consumed). In addition, a library providing access | to another transactional abstraction (e.g. a database supporting transactions) can perform a 2-phase | commit that means that the memory transaction and database transaction either both commit or both | abort. Yes, I have toyed with extending GHC's implementation of STM to support onCommit :: IO a -> STM () The idea is that onCommit would queue up an IO action to be performed when the transaction commits, but without any atomicity guarantee. If the transaction retries, the action is discarded. Now you could say atomic (do { xv <- readTVar x yv <- readTVar y if xv>yv then onCommit launchMissiles else return () }) and the missiles would only get launched when the transaction successfully commits. This is pure programming convenience. It's always possible to make an existing Haskell STM transaction that *returns* an IO action, which is performed by the caller, thus: dO { action <- atomic (do { xv <- readTVar x; yv <- readTVar y; if xv>yv then retur launchMissiles else return (return ()) }) ; action } All onCommit does is make it more convenient. Perhaps a *lot* more convenient. I have also toyed with adding retryWith :: IO a -> STM () The idea here is that the transction is undone (i.e. just like the 'retry' combinator), then the specified action is performed, and then the transaction is retried. Again no atomicity guarantee. If there's an orElse involved, both actions would get done. Unlike onCommit, onRetry adds new power. Suppose you have a memory buffer, with an STM interface: getLine :: Buffer -> STM STring This is the way to do transactional input: if there is not enough input, the transaction retries; and the effects of getLine aren't visible until the transaction commits. The problem is that if there is not enough data in the buffer, getLine will retry; but alas there is no way at present to "tell" someone to fill the buffer with more data. onRetry would fix that. getLine could say if <not enough data> then retryWith <fill-buffer action> It would also make it possible to count how many retries happened: atomic (<transaction> `orElse` retryWith <increment retry counter>) I have not implemented either of these, but I think they'd be cool. Simon PS: I agree wholeheartedly with this: | Of course, these solutions don't deal with the question of atomic blocks that want to perform output | (e.g. to the console) and receive input in response to that. My view at the moment is _that does not | make sense in an atomic block_ -- the output and input can't be performed atomically because the | intervening state must be visible for the user to respond to.

On Fri, Nov 24, 2006 at 08:22:36AM +0000, Simon Peyton-Jones wrote:
I have also toyed with adding
retryWith :: IO a -> STM ()
The idea here is that the transction is undone (i.e. just like the 'retry' combinator), then the specified action is performed, and then the transaction is retried. Again no atomicity guarantee. If there's an orElse involved, both actions would get done.
Unlike onCommit, onRetry adds new power. Suppose you have a memory buffer, with an STM interface: getLine :: Buffer -> STM STring
[Sorry for a long email, I had no time to make it short ;-)] Another example would be my experiments with supporting time in STM, ie. functions: retryIfBefore :: UTCTime -> STM () retryIfAfter :: UTCTime -> STM () (Current code can be obtained with "darcs get" from http://www.uncurry.com/haskell/stm-time/. BTW, shout if you want such a library - it will motivate me to finally release it officially). The naive implementation could hold UTCTime in a single TVar and update this variable in a loop, say, 100 times a second. Of course, with many threads using retryIfBefore/retryIfAfter this would cause too many retries. In my implementation I split the time TVar into a list of TVars, each holding a bit of time representation. The retryIf* functions are written in such a way, that they retry as soon as they can tell that it's too early or too late. This way the number of retries for (retryIfBefore then) is at most the length of suffix of bits that differ in representation of "now" and "then". But there is still a problem with accuracy. Ideally, we would like to be as accurate as possible. One solution goes like this: if retryIfBefore retries because the time value stored in variables is too low, let's allow it to notify the manager thread what UTCTime it is waiting for, so it can schedule to update the variables exactly at this moment. That's where retryWith would help. Right now I am using something named autonomous transactions: autonomously :: Bool -> STM a -> STM () This basically forks a new thread to perform the given transaction outside of the current transaction. To be fair, I am not sure it is sound - as you can imagine, the implementation uses some dirty tricks like unsafeIOToSTM. I haven't checked what would happen if I used some variables created in the surrounding transaction. BTW, implementing STM.Time was very instructive for me. It made me realize that I didn't understand STM as well as I thought. Perhaps it could be made in a nice tutorial, if it wasn't so riddled with unsafish stuff: unsafeIOToSTM mentioned above, and unsafePerformIO used to initialize a top-level variable *and* spawn a manager thread. Here retryWith could also help - I fork the manager thread with it.
I have not implemented either of these, but I think they'd be cool.
I agree especially about retryWith. But I think it's name should include a "danger! sign", because when used wrong, it can "break" the nice properties of STM and cause very surprising bugs. For me one good "danger" indicator is "IO", so perhaps "retryWithIO" ? Best regards Tomasz

On Fri, Nov 24, 2006 at 10:02:59AM +0100, Tomasz Zielonka wrote:
That's where retryWith would help. Right now I am using something named autonomous transactions:
autonomously :: Bool -> STM a -> STM ()
This basically forks a new thread to perform the given transaction outside of the current transaction.
Forgot to explain this Bool parameter: it controls whether the enclosing transaction is waiting for the autonomous transaction to finish. I don't really like this idea, but it allowed to gain some small efficiency advantage, decreasing the number of retries. Best regards Tomasz

I was inspired by Simon's post to kludge up a working prototype that does what is discussed: Simon Peyton-Jones wrote:
| The basic idea is to provide a way for a transaction to call into transaction-aware libraries. The libraries | can register callbacks for if the transaction commits (to actually do any "O") and for if the transaction | aborts (to re-buffer any "I" that the transaction has consumed). In addition, a library providing access | to another transactional abstraction (e.g. a database supporting transactions) can perform a 2-phase | commit that means that the memory transaction and database transaction either both commit or both | abort.
Yes, I have toyed with extending GHC's implementation of STM to support
onCommit :: IO a -> STM ()
The idea is that onCommit would queue up an IO action to be performed when the transaction commits, but without any atomicity guarantee. If the transaction retries, the action is discarded. Now you could say
I have also toyed with adding
retryWith :: IO a -> STM ()
The idea here is that the transction is undone (i.e. just like the 'retry' combinator), then the specified action is performed, and then the transaction is retried. Again no atomicity guarantee. If there's an orElse involved, both actions would get done.
It would also make it possible to count how many retries happened: atomic (<transaction> `orElse` retryWith <increment retry counter>)
I have not implemented either of these, but I think they'd be cool.
Simon
The prototype is:
{- November 24th, 2006
Demonstration Code by Chris Kuklewicz

I posted an improved version of the new monad to the wiki at http://haskell.org/haskellwiki/New_monads/MonadAdvSTM Observations: ** This idiom made it easy for the retrying case to queue an action which ensures success in the next attempt. ** More than one operation can be queued for both the commit and the retry possibilities. ** Reading the TVar in the onRetry/retryWith branch sees the "rolled back" value, which luckily is the initialization value instead of undefined in the case where the TVar was created in the aborted block. ** The new code includes unlift* operations which makes the STM code in testUnlift much easier to write. The relevant example its output are now: -- Example code using the above, lifting into MonadAdvSTM: test ::(Monad m, MonadAdvSTM m) => TVar Bool -> m [Char] test todo = do onCommit (print "onCommit Start") onRetry (print "onRetry Start") v <- liftAdv $ newTVar 7 liftAdv $ writeTVar v 42 onCommit (atomically (readTVar v) >>= \x->print ("onCommit v",x)) onRetry (atomically (readTVar v) >>= \x->print ("onRetry v",x)) choice <- liftAdv $ readTVar todo case choice of True -> return "foo" False -> retryWith $ do atomically (writeTVar todo True) print "Flipped choice to True to avoid infinite loop" -- Same example as test, but unlifting from AdvSTM testUnlift :: TVar Bool -> AdvSTM [Char] testUnlift todo = do onCommit <- unlift1 onCommit onRetry <- unlift1 onRetry retryWith <- unlift1 retryWith liftAdv $ do onCommit (print "onCommit Start") onRetry (print "onRetry Start") v <- newTVar 7 writeTVar v 42 onCommit (atomically (readTVar v) >>= \x->print ("onCommit v",x)) onRetry (atomically (readTVar v) >>= \x->print ("onRetry v",x)) choice <- readTVar todo case choice of True -> return "foo" False -> retryWith $ do atomically (writeTVar todo True) print "Flipped choice to True to avoid infinite loop" -- Example similar to Simon's suggested example: countRetries :: (MonadAdvSTM m, Monad m, Enum a) => IORef a -> m a1 -> m a1 countRetries ioref action = let incr = do old <- readIORef ioref writeIORef ioref $! (succ old) in action `orElseAdv` (retryWith incr) -- Load this file in GHCI and execute main to run the test: main = do counter <- newIORef 0 todo <- newTVarIO False print "test" result <- runAdvSTM (countRetries counter $ test todo) retries <- readIORef counter print ("result",result,"retries",retries) atomically (writeTVar todo False) print "testUnlift" result <- runAdvSTM (countRetries counter $ testUnlift todo) retries <- readIORef counter print ("result",result,"retries",retries) print "bye world" The output in GHCI is *AdvSTM> main "test" "onRetry Start" ("onRetry v",7) "Flipped choice to True to avoid infinite loop" "onCommit Start" ("onCommit v",42) ("result","foo","retries",1) "testUnlift" "onRetry Start" ("onRetry v",7) "Flipped choice to True to avoid infinite loop" "onCommit Start" ("onCommit v",42) ("result","foo","retries",2) "bye world"

I have also toyed with adding
retryWith :: IO a -> STM ()
The idea here is that the transction is undone (i.e. just like the 'retry' combinator), then the specified action is performed, and then the transaction is retried. Again no atomicity guarantee. If there's an orElse involved, both actions would get done.
Unlike onCommit, onRetry adds new power. Suppose you have a memory buffer, with an STM interface: getLine :: Buffer -> STM STring
This is the way to do transactional input: if there is not enough input, the
Simon Peyton-Jones wrote: transaction retries; and the effects of getLine aren't visible until the transaction commits. The problem is that if there is not enough data in the buffer, getLine will retry; but alas there is no way at present to "tell" someone to fill the buffer with more data.
onRetry would fix that. getLine could say if <not enough data> then retryWith <fill-buffer action>
It would also make it possible to count how many retries happened: atomic (<transaction> `orElse` retryWith <increment retry counter>)
I have not implemented either of these, but I think they'd be cool.
Simon
After seeing how close I could come to creating onRetry/retryWith I have a question about the semantics of your idea for retryWith. Normally after a retry the STM block is rolled back and put to sleep and will only be awakened and re-executed if one of the STM variables it had read from is committed to by a different STM block. What about retryWith ? Will the STM block be put to sleep under the same conditions? Can the IO action given to retryWith include commits to STM variables?

| Normally after a retry the STM block is rolled back and put to sleep and will | only be awakened and re-executed if one of the STM variables it had read from is | committed to by a different STM block. The *semantics* are that it is retried anytime in the future. The *pragmatics* are as you describe. | What about retryWith ? Will the STM block be put to sleep under the same | conditions? Can the IO action given to retryWith include commits to STM variables? The semantics are the same as before: the action passed to retryWith is run, and the block is retried anytime in the future. The pragmatics are the same: the action passed to retryWith is run, and the block is put to sleep only to be awakened if one of the STM variables it has read from has been written to -- which could have happened already if the IO action did so. Simon

Hi,
After seeing how close I could come to creating onRetry/retryWith I have a question about the semantics of your idea for retryWith.
Normally after a retry the STM block is rolled back and put to sleep and will only be awakened and re-executed if one of the STM variables it had read from is committed to by a different STM block.
What about retryWith ? Will the STM block be put to sleep under the same conditions? Can the IO action given to retryWith include commits to STM variables?
Starting with this last question -- yes, the example of an STM GetLine using retryWith to pull more input into a buffer relies on an atomic block in the IO action to update the buffer. There are some interesting questions to think about the semantics of "retryWith". The semantics of "retry" in the PPoPP paper say nothing about putting threads to sleep -- it would be correct for an implementation to spin repeatedly executing an "atomic" block until it completes without calling "retry". What should happen with "retryWith" -- should we introduce blocking & wake-up into the semantics, or say that the "retryWith" actions are collected together, executed in place of the transaction (if it does ultimately retry) and then the transaction re-attempted? For simplicity (and to leave flexibility to the implementation) I'd prefer to keep blocking & wake-up out of the semantics. Taking that option, suppose we have "atomic { X }" and X retries with IO action Y. I think I'm saying that that would be equivalent to "Y ; atomic { X }". What are the consequences of this? In the GetLine example it means that an implementation that does put threads to sleep must detect conflicts between the first execution of X and any transactions performed in Y. Are there any interesting problems that come up if "Y" performs transactions that use "retry" or "retryWith"? Tim

Here I restate what you obviously know several times, then take a shot at answering your final question. Tim Harris (RESEARCH) wrote:
Hi,
After seeing how close I could come to creating onRetry/retryWith I have a question about the semantics of your idea for retryWith.
Normally after a retry the STM block is rolled back and put to sleep and will only be awakened and re-executed if one of the STM variables it had read from is committed to by a different STM block.
What about retryWith ? Will the STM block be put to sleep under the same conditions? Can the IO action given to retryWith include commits to STM variables?
Starting with this last question -- yes, the example of an STM GetLine using retryWith to pull more input into a buffer relies on an atomic block in the IO action to update the buffer.
That makes such (atomic X) actions which call (retryWith Y) useful, but will require changing the runtime to do efficiently if the (Y) action does not allow the (atomic X) to succeed/commit on the next attempt. Imaging that getLine does not block and returns no input, so (Y) does not feed (X). Then the next attempt to do (X) will (retryWith Y) and (Y) still fails to get input, so you have a "busy wait" where (Y) and (X) alternately execute. It will require a runtime change to prevent (X) from being retried until more input appears. In pseudocode this would be: X = if tchan is empty then retryWith Y else do work and commit Y = if input is available then feed tchan else return ()
There are some interesting questions to think about the semantics of
What should happen with "retryWith" -- should we introduce blocking & wake-up into the semantics, or say that the "retryWith" actions are collected together, executed in place of the transaction (if it does ultimately retry) and
For simplicity (and to leave flexibility to
"retryWith". The semantics of "retry" in the PPoPP paper say nothing about putting threads to sleep -- it would be correct for an implementation to spin repeatedly executing an "atomic" block until it completes without calling "retry". It would indeed be semantically correct, but if you have many spinning threads then the program will grind to a halt and few people would be able to employ STM. So the spec need not mention the blocking, but it should be possible to implement it that way. And GHC does. And onCommit can be implemented without changing from blocking to spinning, while retryWith does change from blocking to spinning (without a runtime change) then the transaction re-attempted? Since (retryWith y1) `orElse` (retryWith y2) must execute y1 and y2, I used onRetry to collect such actions: "retryWith io = onRetry io >> retry". After running all the onRetry actions it immediately re-attempts the whole atomic transation without regard for whether any STM variables have been updated, so this causes spinning. [ Aside: I probably will modify it so that a lack of onRetry actions will prevent spinning. ] the implementation) I'd prefer to keep blocking & wake-up out of the semantics.
Taking that option, suppose we have "atomic { X }" and X retries with IO action Y. I think I'm saying that that would be equivalent to "Y ; atomic { X }". What are the consequences of this?
Bad consequences. In particular, Y must finish before X is re-attempted. My implementation does this at the moment, which is bad, but the right solution requires a runtime change.
In the GetLine example it means that an implementation that does put threads to sleep must detect conflicts between the first execution of X and any transactions performed in Y.
There may also be a distinction for whether [Existing/retry] If atomic { X } fails with a normal retry then rollback and put X to sleep until an appropriate STM update [Existing/fail] If atomic { X } fails with from a conflicting update then rollback and immediately re-attempt X [New case/retry] If atomic { X } fails with (retryWith Y) then rollback and put X to sleep until an appropriate STM update and then schedule (Y) (e.g. with forkIO). [New case/fail a] If atomic { X } fails with a conflicting update and has a pending (onRetry Y) then rollback and schedule both Y and a re-attempt of X. This last case comes from imagining using orElse: (code calls retryWith Y) `orElse` (code that causes conflicting update) in which case running Y seems like the obvious thing to do.
Are there any interesting problems that come up if "Y" performs transactions
that use "retry" or "retryWith"?
Tim
In many useful cases, such as the getLine example, the Y action will have its own atomic {} block. In which case the semantics of when it is allowed to re-attempt X are what is important. If you require (Y) to complete before re-attempting (X) then you get an infinite regression where every (atomic block) fails with (retryWith (next atomic block)), and nothing is ever re-attempted. This is why "retryWith Y" meaning rollback X and do "Y >> atomic X" is the wrong implementation. If one takes "retryWith Y" to mean rollback X and do "forkIO Y >> atomic X" then one might spawn many many copies of Y waiting for atomic X to do something novel. Even if Y does not use retry/retryWith it can fail if it writes a conflicting update to an STM variable. Since we want Y to be able to commit updates to STM variables then Y can implicitly fail and retry. So the semantics must be what I said above, which implicitly allow X to be re-attempted as soon as anything performs an STM update without requiring the retryWith actions to finish first. One could imagine (atomic X) fails via (retryWith Y). X is put to sleep and Y is scheduled to run. Meanwhile another action Z executes and commits and updates whatever X is waiting on. So X is awakened and runs and commits. And only later does (Y) execute. -- Chris

| In many useful cases, such as the getLine example, the Y action will have its | own atomic {} block. In which case the semantics of when it is allowed to | re-attempt X are what is important. If you require (Y) to complete before | re-attempting (X) then you get an infinite regression where every (atomic block) | fails with (retryWith (next atomic block)), and nothing is ever re-attempted. | This is why "retryWith Y" meaning rollback X and do "Y >> atomic X" is the wrong | implementation. I don't agree. I think it's quite reasonable. Not many atomic blocks will finish with retryWith. Of course there is a possibility of an infinite loop, but we already have that: f x = f x. Of course, Y can always choose to do a forkIO, but it shouldn't hav to. For me the only difficulty is the implementation. We'd like to block X on the TVars it read (as usual), *unless* executing Y wrote to any of them. That requires a bit more cleverness in the commit code, but not a great deal I think. Simon

Eureka, I claim to have written an implementation which agrees with all the semantics that Simon Peyton-Jones wants for onCommit/onRetry/retryWith. See below: Simon Peyton-Jones wrote:
| In many useful cases, such as the getLine example, the Y action will have its | own atomic {} block. In which case the semantics of when it is allowed to | re-attempt X are what is important. If you require (Y) to complete before | re-attempting (X) then you get an infinite regression where every (atomic block) | fails with (retryWith (next atomic block)), and nothing is ever re-attempted. | This is why "retryWith Y" meaning rollback X and do "Y >> atomic X" is the wrong | implementation.
I don't agree. I think it's quite reasonable. Not many atomic blocks will finish with retryWith. Of course there is a possibility of an infinite loop, but we already have that: f x = f x. Of course, Y can always choose to do a forkIO, but it shouldn't hav to.
For me the only difficulty is the implementation. We'd like to block X on the TVars it read (as usual), *unless* executing Y wrote to any of them. That requires a bit more cleverness in the commit code, but not a great deal I think.
Simon
It is the Helper Thread code version on the wiki at http://haskell.org/haskellwiki/New_monads/MonadAdvSTM#Helper_Thread_Code Quick explanation of the code for runAdvSTM (usually called with atomicAdv): When the action X in (atomicAdv X) ends with (retryWith Y) the job Y is put into an MVar. Then a retry causes the orElse in wrappedAction to perform check'retry. This sees the job Y and then *) if this is the first retry job: creates and cache a channel and spawn the helper thread *) push the retry job Y into the channel *) call retry to cause action X to cause the current GHC runtime to block on whatever STM-variables it used The wrappedAction commits if and only if the action X commits. In which case the commit action stored in the TVar is read and performed. Then a check is performed to see if the helper thread was spawned, and if so tell the helper thread to quit and block until the helper thread is done. Note that the action X can be re-attempted by the runtime before the retry job Y is run or before it has finished running. But this will only happen in the usual cases where there was an STM update, instead of the possible busy wait in the Single Thread code example on the wiki page. Does this meet your specifications, Simon? -- Chris

this thread reminds me about something that I wanted to ask you. if I recall correctly, most of the literature references in STM papers are recent, so I wondered whether you are aware of this one: NAMING AND SYNCHRONIZATION IN A DECENTRALIZED COMPUTER SYSTEM SourceTechnical Report: TR-205 Year of Publication: 1978 Author D. P. Reed I'm not entirely sure where I got my version from (it was mentioned as a cornerstone in Alan Kay et al s latest project, Croquet, on which Reed is a collaborator: http://www.opencroquet.org/ ), but here is the abstract: http://portal.acm.org/citation.cfm?coll=GUIDE&dl=GUIDE&id=889815 (note that it mentions both grouping of updates, and synchronized composition of modules with local synchronization constraints) and this might be the official site for the scanned copy (?): http://www.lcs.mit.edu/publications/specpub.php?id=773 just wondering, claus

Interesting reference. I had never heard of it. From reading section 1.2 it sounds like an early description of the optimistic approach to implementing atomic transactions (which is itself a well-studied field). Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Claus | Reinke | Sent: 24 November 2006 12:22 | To: Simon Peyton-Jones; Tim Harris (RESEARCH) | Cc: haskell-cafe@haskell.org | Subject: Re: [Haskell] Re: [Haskell-cafe] SimonPJ and Tim Harris explain STM- video | | this thread reminds me about something that I wanted to ask you. | if I recall correctly, most of the literature references in STM papers | are recent, so I wondered whether you are aware of this one: | | NAMING AND SYNCHRONIZATION IN A | DECENTRALIZED COMPUTER SYSTEM | | SourceTechnical Report: TR-205 | Year of Publication: 1978 | Author D. P. Reed | | I'm not entirely sure where I got my version from (it was mentioned | as a cornerstone in Alan Kay et al s latest project, Croquet, on which | Reed is a collaborator: http://www.opencroquet.org/ ), but here is | the abstract: | | http://portal.acm.org/citation.cfm?coll=GUIDE&dl=GUIDE&id=889815 | | (note that it mentions both grouping of updates, and synchronized | composition of modules with local synchronization constraints) | | and this might be the official site for the scanned copy (?): | | http://www.lcs.mit.edu/publications/specpub.php?id=773 | | just wondering, | claus | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

also on the multi-version approach. but the particular reason I mentioned this was that it also tried to address the issue of composing transactions (discussion of which is explicitly excluded from the section 1.2 you refer to). for instance, compare the discussion and examples in "Composable Memory Transactions" with the one in section 3.11 (pp 80-) of Reed's thesis. not that STM isn't nicer, more complete, and all that;-) but Reed's ideas seemed rather more advanced than I had expected from the discussion of related work in the STM paper. Claus
Interesting reference. I had never heard of it. From reading section 1.2 it sounds like an early description of > the optimistic approach to implementing atomic transactions (which is itself a well-studied field).
Simon
| NAMING AND SYNCHRONIZATION IN A | DECENTRALIZED COMPUTER SYSTEM | | SourceTechnical Report: TR-205 | Year of Publication: 1978 | Author D. P. Reed | | I'm not entirely sure where I got my version from (it was mentioned | as a cornerstone in Alan Kay et al s latest project, Croquet, on which | Reed is a collaborator: http://www.opencroquet.org/ ), but here is | the abstract: | | http://portal.acm.org/citation.cfm?coll=GUIDE&dl=GUIDE&id=889815 | | (note that it mentions both grouping of updates, and synchronized | composition of modules with local synchronization constraints) | | and this might be the official site for the scanned copy (?): | | http://www.lcs.mit.edu/publications/specpub.php?id=773

Hi,
On 23/11/06, Benjamin Franksen
One answer is in fact "to make it so that Console.Write can be rolled back too". To achieve this one can factor the actual output to another task and inside the transaction merely send the message to a transactional channel (TChan):
So, you could simply return the console output as (part of) the result of the atomic action. Wrap it in a WriterT monad transformer, even. (one, console) <- atomic $ runWriterT $ do tell "hello world\n" return 1 putStr console (Not terribly efficient, but you get the idea.) You're just calculating what output to make inside the transaction; the actual outputting happens outside, once the transaction commits.
Another task regularly takes messages from the channel
With STM, the outputter task won't see any messages from the channel until your main atomic block completes, after which you're living in IO-land, so you might as well do the output yourself. Pugs/Perl 6 takes the approach that any IO inside an atomic block raises an exception.
Unfortunately I can't see how to generalize this to input as well...
The dual of how you described the output situation: read a block of input before the transaction starts, and consume this during the transaction. I guess you're not seeing how this generalises because potentially you won't know how much of the input you will need to read beforehand... (so read all available input?(!) You have the dual situation in the output case, in that you can't be sure how much output it may generate / you will need to buffer.) input <- hGetContent file atomic $ flip runReaderT input $ do input <- ask -- do something with input return 42 (This is actually a bad example, since hGetContents reads the file lazily with interleaved IO...) later, /Liyang

Hi Liyang HU you wrote:
On 23/11/06, Benjamin Franksen
wrote: One answer is in fact "to make it so that Console.Write can be rolled back too". To achieve this one can factor the actual output to another task and inside the transaction merely send the message to a transactional channel (TChan):
So, you could simply return the console output as (part of) the result of the atomic action. Wrap it in a WriterT monad transformer, even.
But this would break atomicity, wouldn't it? Another call to doSomething from another task could interrupt before I get the chance to do the actual output. With a channel whatever writes will happen in the same order in which the STM actions commit (which coincides with the order in which the counters get incremented).
Another task regularly takes messages from the channel
With STM, the outputter task won't see any messages from the channel until your main atomic block completes, after which you're living in IO-land, so you might as well do the output yourself.
Yeah, right. Separate task might still be preferable, otherwise you have to take care not to forget to actually do the IO after each transaction. I guess it even makes sense to hide the channel stuff behind some nice abstraction, so inside the transaction it looks similar to a plain IO action: output port msg The result is in fact mostly indistiguishable from a direct IO call due to the fact that IO is buffered in the OS anyway.
Pugs/Perl 6 takes the approach that any IO inside an atomic block raises an exception.
Unfortunately I can't see how to generalize this to input as well...
The dual of how you described the output situation: read a block of input before the transaction starts, and consume this during the transaction. I guess you're not seeing how this generalises because potentially you won't know how much of the input you will need to read beforehand... (so read all available input?(!) You have the dual situation in the output case, in that you can't be sure how much output it may generate / you will need to buffer.)
You say it. I guess the main difference is that I have a pretty good idea how much data is going to be produced by my own code, and if it's a bit more than I calculated then the whole process merely uses up some more memory, which is usually not a big problem. However, with input things are different: in many cases the input length is not under my control and could be arbitrarily large. If I read until my buffer is full and I still haven't got enough data, my transaction will be stuck with no way to demand more input. (however, see below)
input <- hGetContent file atomic $ flip runReaderT input $ do input <- ask -- do something with input return 42
(This is actually a bad example, since hGetContents reads the file lazily with interleaved IO...)
In fact reading everything lazily seems to be the only way out, if you don't want to have arbitrary limits for chunks of input. OTOH, maybe limiting the input chunks to some maximum length is a good idea regardless of STM and whatnot. Some evil data source may want to crash my process by making it eat more and more memory... So, after all you are probably right and there is an obvious generalization to input. Cool. Cheers Ben

Hallo,
On 24/11/06, Benjamin Franksen
So, you could simply return the console output as (part of) the result of the atomic action. Wrap it in a WriterT monad transformer, even. But this would break atomicity, wouldn't it?
In the sense as you just described, yes. You're right: there's no guarantee that something else might not jump in between the call to atomic and the following putStr, so the TVar changes in the atomic block no longer take place in step with the output actions.
I have a pretty good idea how much data is going to be produced by my own code, and if it's a bit more than I calculated then the whole process merely uses up some more memory, which is usually not a big problem. However, with input things are different:
Really? I'd have said that I have a pretty good idea how much data is going to be consumed by my own code, and if it's a bit more than I calculated then I'd merely read some more at the beginning (putting any unused bits back on the input queue afterwards of course), which is usually not a big problem. :) Yes, I do get your point. It's easier to allocate a larger buffer for your output as needed, than to anticipate how much input you might require. I'd still claim they're different instances of the same scheme though!
[If] I still haven't got enough data, my transaction will be stuck with no way to demand more input.
Take your output channel idea, and use that for input too? (Separate thread to read the input and place it at the end of some queue.) You would basically retry and block (or rather, STM would do the latter for you) if you haven't enough data, until more came along. Cheers, /Liyang

Liyang HU wrote:
On 24/11/06, Benjamin Franksen
wrote: I have a pretty good idea how much data is going to be produced by my own code, and if it's a bit more than I calculated then the whole process merely uses up some more memory, which is usually not a big problem. However, with input things are different:
Really? I'd have said that I have a pretty good idea how much data is going to be consumed by my own code, and if it's a bit more than I calculated then I'd merely read some more at the beginning (putting any unused bits back on the input queue afterwards of course), which is usually not a big problem. :)
Yes, I do get your point. It's easier to allocate a larger buffer for your output as needed, than to anticipate how much input you might require. I'd still claim they're different instances of the same scheme though!
[If] I still haven't got enough data, my transaction will be stuck with [no way to demand more input.
Take your output channel idea, and use that for input too? (Separate thread to read the input and place it at the end of some queue.) You would basically retry and block (or rather, STM would do the latter for you) if you haven't enough data, until more came along.
Right. I couldn't see it at first but the I and O really are dual to each other. Thanks for pointing this out -- it seems STM is even more useful than I thought. Cheers Ben

I would just love to have some Haskell video casts. That would be awesome! Cheers, Johan On 11/23/06, Bayley, Alistair wrote:
http://channel9.msdn.com/Showpost.aspx?postid=231495
The links to the video are a couple of yellow buttons at the bottom of the article: "Watch" or "Download".
I haven't watched this yet (it's nearly an hour long, I think). Found via reddit (http://reddit.com).
Haskeller's on TV (sort of...) woot woot!
Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. ***************************************************************** _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Nov 23, 2006 at 12:56:00PM -0000, Bayley, Alistair wrote:
http://channel9.msdn.com/Showpost.aspx?postid=231495
The links to the video are a couple of yellow buttons at the bottom of the article: "Watch" or "Download".
I haven't watched this yet (it's nearly an hour long, I think). Found via reddit (http://reddit.com).
Haskeller's on TV (sort of...) woot woot!
Does anybody know how to watch this on Linux? I would prefer to simply download the movie file and use MPlayer on that, but I failed. .. or on Mac OS X (haven't tried yet) Best regards Tomasz

On 11/24/06, Tomasz Zielonka
On Thu, Nov 23, 2006 at 12:56:00PM -0000, Bayley, Alistair wrote:
http://channel9.msdn.com/Showpost.aspx?postid=231495
The links to the video are a couple of yellow buttons at the bottom of the article: "Watch" or "Download".
I haven't watched this yet (it's nearly an hour long, I think). Found via reddit (http://reddit.com).
Haskeller's on TV (sort of...) woot woot!
Does anybody know how to watch this on Linux? I would prefer to simply download the movie file and use MPlayer on that, but I failed.
.. or on Mac OS X (haven't tried yet)
Worked for me with mplayer+w32codecs. -- Cheers, Lemmih
participants (12)
-
Bayley, Alistair
-
Benjamin Franksen
-
Cale Gibbard
-
Chris Kuklewicz
-
Claus Reinke
-
Jason Dagit
-
Johan Tibell
-
Lemmih
-
Liyang HU
-
Simon Peyton-Jones
-
Tim Harris (RESEARCH)
-
Tomasz Zielonka