
Hello Cafe I'm currently writing an app with heavy use of message passing. To see which messages takes most of the bandwidth I wrote the following code: -- data Counter = CNT !Int !Int !Int !Int cntMsg (CNT a b c d) (MoveOther _ _) = (CNT a+1 b c d) cntMsg (CNT a b c d) (MoveSelf _) = (CNT a b+1 c d) cntMsg (CNT a b c d) (NilMsg) = (CNT a b c+1 d) cntMsg (CNT a b c d) (RoundEnd) = (CNT a b c d+1) emptyCnt = CNT 0 0 0 0 showCnt (CNT a b c d) = printf "CNT MoveOther=%d MoveSelf=%d NilMsg=%d RoundEnd=%d" a b c d -- The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,()))) Running it without increased stack blows it. With 200M stack I get after a second or so: CNT MoveOther=2125764 MoveSelf=0 NilMsg=0 RoundEnd=2916 The datatype itself is strict. So where is the thunk actually accumulating? Best regards Christopher Skrzętnicki

Krzysztof Skrzętnicki wrote:
The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,())))
atomicModifyIORef does not force the new value of the IORef. If the previous contents of the IORef is x, the new contents will be a thunk, (\ cnt -> (cntMsg cnt msg,())) x You can try forcing the new value, say by adding
readIORef ioref >>= (return $!)
after the atomicModifyIORef.
The datatype itself is strict. So where is the thunk actually accumulating?
In the IORef. HTH, Bertram

I wrote:
Krzysztof Skrzętnicki wrote:
The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,())))
atomicModifyIORef does not force the new value of the IORef. If the previous contents of the IORef is x, the new contents will be a thunk,
(\ cnt -> (cntMsg cnt msg,())) x
Sorry, it's slightly worse than that. The contents becomes sel_0 (\ cnt -> (cntMsg cnt msg, ())) x where sel_0 is basically an RTS internal version of fst. Instead of reading the new value of the IORef, you could also force the old one: atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg, msg)) >>= (return $!) Bertram

2009/5/27 Bertram Felgenhauer
I wrote:
Krzysztof Skrzętnicki wrote:
The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,())))
atomicModifyIORef does not force the new value of the IORef. If the previous contents of the IORef is x, the new contents will be a thunk,
(\ cnt -> (cntMsg cnt msg,())) x
Sorry, it's slightly worse than that. The contents becomes
sel_0 (\ cnt -> (cntMsg cnt msg, ())) x
where sel_0 is basically an RTS internal version of fst.
Instead of reading the new value of the IORef, you could also force the old one:
atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg, msg)) >>= (return $!)
Thanks for the tip, although it seems tricky to get it right. I wonder why there is no strict version of atomicModifyIORef? Dually there might be a strict version of IORef datatype. Best regards Christopher Skrzętnicki

Thanks for the tip, although it seems tricky to get it right. I wonder why there is no strict version of atomicModifyIORef? Dually there might be a strict version of IORef datatype.
Alternatively, you could use STM, where you can write your own atomic update function, which has the strictness you need (untested): import Control.Concurrent.STM strictUpdate :: (a->a) -> TVar a -> STM () strictUpdate f v = do x <- readTVar v let x1 = f x x1 `seq` writeTVar v x1 g :: (Int->Int) -> TVar Int -> IO () g f v = atomically (strictUpdate f v) Tim

Krzysztof Skrzętnicki wrote:
2009/5/27 Bertram Felgenhauer
: I wrote:
Krzysztof Skrzętnicki wrote:
The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,())))
atomicModifyIORef does not force the new value of the IORef. If the previous contents of the IORef is x, the new contents will be a thunk,
(\ cnt -> (cntMsg cnt msg,())) x
Sorry, it's slightly worse than that. The contents becomes
sel_0 (\ cnt -> (cntMsg cnt msg, ())) x
where sel_0 is basically an RTS internal version of fst.
Instead of reading the new value of the IORef, you could also force the old one:
atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg, msg)) >>= (return $!)
Thanks for the tip, although it seems tricky to get it right. I wonder why there is no strict version of atomicModifyIORef?
Something like this? -- | Stricter version of 'atomicModifyIORef', which prevents building -- up huge thunks in the 'IORef' due to repeated modification. -- Unlike 'atomicModifyIORef', 'atomicModifyIORef'' may block. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b atomicModifyIORef' ioref f = do res <- atomicModifyIORef ioref f new <- readIORef ioref new `seq` return res (The step that may block is forcing the new value - if another thread is already evaluating part of the thunk, the currently executing thread will block, waiting for the other thread to finish.)
Dually there might be a strict version of IORef datatype.
One interesting feature of atomicModifyIORef is that its implementation is lock-free, and never blocks (which affects exception handling): replacing the old value by the new value is done with compare-and-swap operation in a tight loop. Each iteration executes very quickly because all it does is replace the reference to the old value in the new thunk. With a strict IORef, the time window between reading the old value and storing the new value would become arbitrarily large, because you'd have to force the new value before exchanging it with the old value. So a reasonable implementation would have to use locks instead, I think, making atomicModifyIORef more expensive, and less useful in contexts that block exceptions. Bertram

On Thu, May 28, 2009 at 14:41, Bertram Felgenhauer
Krzysztof Skrzętnicki wrote:
2009/5/27 Bertram Felgenhauer
: I wrote:
Krzysztof Skrzętnicki wrote:
The code for modifying the counter: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,())))
atomicModifyIORef does not force the new value of the IORef. If the previous contents of the IORef is x, the new contents will be a thunk,
(\ cnt -> (cntMsg cnt msg,())) x
Sorry, it's slightly worse than that. The contents becomes
sel_0 (\ cnt -> (cntMsg cnt msg, ())) x
where sel_0 is basically an RTS internal version of fst.
Instead of reading the new value of the IORef, you could also force the old one:
atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg, msg)) >>= (return $!)
Thanks for the tip, although it seems tricky to get it right. I wonder why there is no strict version of atomicModifyIORef?
Something like this?
-- | Stricter version of 'atomicModifyIORef', which prevents building -- up huge thunks in the 'IORef' due to repeated modification. -- Unlike 'atomicModifyIORef', 'atomicModifyIORef'' may block. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b atomicModifyIORef' ioref f = do res <- atomicModifyIORef ioref f new <- readIORef ioref new `seq` return res
(The step that may block is forcing the new value - if another thread is already evaluating part of the thunk, the currently executing thread will block, waiting for the other thread to finish.)
Dually there might be a strict version of IORef datatype.
One interesting feature of atomicModifyIORef is that its implementation is lock-free, and never blocks (which affects exception handling): replacing the old value by the new value is done with compare-and-swap operation in a tight loop. Each iteration executes very quickly because all it does is replace the reference to the old value in the new thunk.
With a strict IORef, the time window between reading the old value and storing the new value would become arbitrarily large, because you'd have to force the new value before exchanging it with the old value. So a reasonable implementation would have to use locks instead, I think, making atomicModifyIORef more expensive, and less useful in contexts that block exceptions.
We may as well drop the 'atomic' keyword and provide a warning about possible blocking of thread. The end user may forkIO the modification if he wants to. I modified the code as follows, it works now: (\ msg -> atomicModifyIORef ioref (\ cnt -> (cntMsg cnt msg,cnt)) >>= (return $!)) Thank you all for your help! Best regards Christopher Skrzętnicki
participants (3)
-
Bertram Felgenhauer
-
Krzysztof Skrzętnicki
-
Tim Docker