
Hi, My question is regarding the correct us of STM in Haskell. I have put to together a simple example, which represents more verbose code in a library that I am writing. The question is a simple one. Must all operations on a TVar happen within *the same* atomically block, or am I am I guaranteed thread safety if, say, I have a number of atomically blocks in an IO function. Here's my example: http://pastebin.com/Hit5vKmk . Is this example permissible? thanks, -- Rob Stewart

On Fri, Jan 13, 2012 at 10:04 AM, Rob Stewart
The question is a simple one. Must all operations on a TVar happen within *the same* atomically block, or am I am I guaranteed thread safety if, say, I have a number of atomically blocks in an IO function.
If you want successive operations to see a consistent state, they must occur in the same atomically block.

"Bryan O'Sullivan"
The question is a simple one. Must all operations on a TVar happen within *the same* atomically block, or am I am I guaranteed thread safety if, say, I have a number of atomically blocks in an IO function.
If you want successive operations to see a consistent state, they must occur in the same atomically block.
I'm not sure I understand the question, nor the answer? I thought the idea was that state should be consistent on the entry and exit of each "atomically" block. So you can break your program into multiple transactions, but each transaction should be a semantically complete unit. -k -- If I haven't seen further, it is by standing in the footprints of giants

On 01/14/2012 03:55 PM, Ketil Malde wrote:
"Bryan O'Sullivan"
writes: The question is a simple one. Must all operations on a TVar happen within *the same* atomically block, or am I am I guaranteed thread safety if, say, I have a number of atomically blocks in an IO function.
If you want successive operations to see a consistent state, they must occur in the same atomically block.
I'm not sure I understand the question, nor the answer? I thought the idea was that state should be consistent on the entry and exit of each "atomically" block. So you can break your program into multiple transactions, but each transaction should be a semantically complete unit.
I think "consistent state" here means that you can be sure no other thread has modified a, say, TVar, within the current 'atomically' block. E.g. for MVars, you could /not/ be sure that void (takeMVar mvar) >> putMVar mvar 5 won't block if mvar is full at the beginning, because a different thread might put to mvar between the two actions. However, in atomically $ void (takeTVar tvar) >> putTVar tvar 5 , this is not possible, the action after 'atomically' won't be influenced by any other threads while it's running, hence the name. -- Steffen

On 14 January 2012 18:05, Steffen Schuldenzucker
I think "consistent state" here means that you can be sure no other thread has modified a, say, TVar, within the current 'atomically' block.
OK, well take a modified example, where I am wanting to call an IO function within an atomically block: --- import Control.Concurrent.STM import Control.Monad.IO.Class (liftIO) addThree :: TVar Int -> Int -> STM () addThree t = do i <- liftIO three -- Problem line ls <- readTVar t writeTVar t (ls + i) three :: IO Int three = return 3 main :: IO () main = do val <- atomically $ do tvar <- newTVar 0 addThree tvar readTVar tvar putStrLn $ "Value: " ++ show val --- Are IO functions permissible in STM atomically blocks? If so how? If not, how would one get around a problem of having to use an IO function to retrieve a value that is to be written to a TVar ? -- Rob

On 14 January 2012 19:24, Rob Stewart
On 14 January 2012 18:05, Steffen Schuldenzucker
wrote: I think "consistent state" here means that you can be sure no other thread has modified a, say, TVar, within the current 'atomically' block.
OK, well take a modified example, where I am wanting to call an IO function within an atomically block: --- import Control.Concurrent.STM import Control.Monad.IO.Class (liftIO)
addThree :: TVar Int -> Int -> STM () addThree t = do i <- liftIO three -- Problem line ls <- readTVar t writeTVar t (ls + i)
three :: IO Int three = return 3
main :: IO () main = do val <- atomically $ do tvar <- newTVar 0 addThree tvar readTVar tvar putStrLn $ "Value: " ++ show val ---
Are IO functions permissible in STM atomically blocks? If so how? If not, how would one get around a problem of having to use an IO function to retrieve a value that is to be written to a TVar ?
-- Rob
No that's not possible. An STM transaction may be tried several times so allowing IO doesn't make sense. Instead you pass any values that you need into the transaction. e.g. line <- getLine atomically $ do writeTVar v line ... Daniel

On 1/14/12 2:24 PM, Rob Stewart wrote:
Are IO functions permissible in STM atomically blocks?
They are not. The semantics of STM are that each transaction is retried until it succeeds, and that the number of times it is retried does not affect the program output. Thus, you can only do things in STM which can be reverted, since you may have to undo the side-effects whenever the transaction is retried. However, if you're interested in pursuing this approach, you should take a look at TwilightSTM which expands the interaction possibilities between IO and STM.
If so how? If not, how would one get around a problem of having to use an IO function to retrieve a value that is to be written to a TVar ?
If you truly must do IO in the middle of a transaction, the typical solution is to use a locking mechanism. For example, you use a TMVar() as the lock: taking the () token in order to prevent other threads from doing the IO; doing the IO; and then putting the () token back. Thus, something like: do ... atomically $ do ... () <- takeTMVar lockRunFoo x <- runFoo atomically $ do putTMVar lockRunFoo () ...x... ... However, it's often possible to factor the IO out of the original transaction, so you should do so whenever you can. An unfortunate downside of the above locking hack is that the STM state is not guaranteed to be consistent across the two transactions. You can fake read-consistency by moving reads into the first transaction in order to bind the values to local variables, as in: do ... (a,b,c) <- atomically $ do ... a <- ... ... b <- ... ... c <- ... ... () <- takeTMVar lockRunFoo return (a,b,c) x <- runFoo atomically $ do putTMVar lockRunFoo () ...x...a...b...c... ... And you can fake write-consistency by moving writes into the second transaction to ensure that they all are committed at once. However, you can't use those tricks if you have a complicated back and forth with reading and writing. -- Live well, ~wren
participants (6)
-
Bryan O'Sullivan
-
Daniel Waterworth
-
Ketil Malde
-
Rob Stewart
-
Steffen Schuldenzucker
-
wren ng thornton