Timeouts that don't cause data growth.

Trying to understand why the code here: http://moonpatio.com/fastcgi/hpaste.fcgi/view?id=8823#a8823 exhausts memory. I need to have timeouts in a program I'm writing that will run an interactive polling session of some remote resources, and know when to give up and handle that error. Unfortunately this code dies pretty quickly and produces an -hc graph like the one attached. It seems that System.Timeout can't be used for this. I should note that if the code is changed to use an inifnite timeout (-1) that this problem doesn't occur. Is this a bug in System.Timeout, or is there something I should be doing to keep the data size down? Dave

I tried a few things. First I added another timeout to main, so the program kills itself after a few seconds. doit :: IO (Maybe ()) doit = timeout 12000000 $ {- yield >> -} return () main :: IO () main = do _ <- timeout 5000000 $ forever doit return () This program failed to terminate. But when I compiled -with threaded and added a yield to doit, it worked (kinda). If the timeout in doit is not too long, like 200 milliseconds, the program has constant space usage. But when I increased the timeout in doit to 12 seconds I got a stack overflow. I'll investigate further when I have more time. Regards, Roel

Is this just a problem of spawning too many forkIO resources that never produce a result? I was thinking of trying something like the following in System.Timeout's place:
module Main where
import Control.Concurrent.MVar import Control.Concurrent import Data.Maybe
timeout :: Int -> IO a -> IO (Maybe a) timeout time action = do someMVar <- newEmptyMVar -- MVar is a Maybe timeoutThread <- forkIO $ nothingIzer time someMVar forkIO $ actionRunner action someMVar timeoutThread takeMVar someMVar >>= return where nothingIzer time mvar = threadDelay time >> putMVar mvar Nothing actionRunner action mvar timeoutThread = do res <- action killThread timeoutThread putMVar mvar $ Just res
main :: IO () main = do res <- timeout (5 * 10 ^ 6) (getLine >>= putStrLn) case res of Nothing -> putStrLn "Timeout" Just x -> putStrLn "Success"
On Tue, Mar 23, 2010 at 11:31 AM, Roel van Dijk
I tried a few things. First I added another timeout to main, so the program kills itself after a few seconds.
doit :: IO (Maybe ()) doit = timeout 12000000 $ {- yield >> -} return ()
main :: IO () main = do _ <- timeout 5000000 $ forever doit return ()
This program failed to terminate. But when I compiled -with threaded and added a yield to doit, it worked (kinda). If the timeout in doit is not too long, like 200 milliseconds, the program has constant space usage. But when I increased the timeout in doit to 12 seconds I got a stack overflow.
I'll investigate further when I have more time.
Regards, Roel

Actually this isn't good enough either as I'm potentially leaving the
"action" thread in a state where it never times out... I guess I have to do
all thread killing in the main thread.
On Tue, Mar 23, 2010 at 12:23 PM, David Leimbach
Is this just a problem of spawning too many forkIO resources that never produce a result?
I was thinking of trying something like the following in System.Timeout's place:
module Main where
import Control.Concurrent.MVar import Control.Concurrent import Data.Maybe
timeout :: Int -> IO a -> IO (Maybe a) timeout time action = do someMVar <- newEmptyMVar -- MVar is a Maybe timeoutThread <- forkIO $ nothingIzer time someMVar forkIO $ actionRunner action someMVar timeoutThread takeMVar someMVar >>= return where nothingIzer time mvar = threadDelay time >> putMVar mvar Nothing actionRunner action mvar timeoutThread = do res <- action killThread timeoutThread putMVar mvar $ Just res
main :: IO () main = do res <- timeout (5 * 10 ^ 6) (getLine >>= putStrLn) case res of Nothing -> putStrLn "Timeout" Just x -> putStrLn "Success"
On Tue, Mar 23, 2010 at 11:31 AM, Roel van Dijk
wrote: I tried a few things. First I added another timeout to main, so the program kills itself after a few seconds.
doit :: IO (Maybe ()) doit = timeout 12000000 $ {- yield >> -} return ()
main :: IO () main = do _ <- timeout 5000000 $ forever doit return ()
This program failed to terminate. But when I compiled -with threaded and added a yield to doit, it worked (kinda). If the timeout in doit is not too long, like 200 milliseconds, the program has constant space usage. But when I increased the timeout in doit to 12 seconds I got a stack overflow.
I'll investigate further when I have more time.
Regards, Roel

On Tue, Mar 23, 2010 at 8:23 PM, David Leimbach
Is this just a problem of spawning too many forkIO resources that never produce a result?
It looks like it. Lets look at the implementation of timeout: timeout :: Int -> IO a -> IO (Maybe a) timeout n f | n < 0 = fmap Just f | n == 0 = return Nothing | otherwise = do pid <- myThreadId ex <- fmap Timeout newUnique handleJust (\e -> if e == ex then Just () else Nothing) (\_ -> return Nothing) (bracket (forkIO (threadDelay n >> throwTo pid ex)) (killThread) (\_ -> fmap Just f)) We see a thread is forked that throws the Timeout exception to the current thread after n microseconds. However when the current thread finishes early this timeout thread will be killed. I assume that when a thread is killed it can be garbage collected. (However we have to watch out for [1]) So it's a big surprise to me that we're seeing this space-leak! Maybe you can file a bug report?
I was thinking of trying something like the following in System.Timeout's place:
module Main where import Control.Concurrent.MVar import Control.Concurrent import Data.Maybe
timeout :: Int -> IO a -> IO (Maybe a) timeout time action = do someMVar <- newEmptyMVar -- MVar is a Maybe timeoutThread <- forkIO $ nothingIzer time someMVar forkIO $ actionRunner action someMVar timeoutThread takeMVar someMVar >>= return where nothingIzer time mvar = threadDelay time >> putMVar mvar Nothing actionRunner action mvar timeoutThread = do res <- action killThread timeoutThread putMVar mvar $ Just res main :: IO () main = do res <- timeout (5 * 10 ^ 6) (getLine >>= putStrLn) case res of Nothing -> putStrLn "Timeout" Just x -> putStrLn "Success"
The original timeout obeys the following specification: "The design of this combinator was guided by the objective that timeout n f should behave exactly the same as f as long as f doesn't time out. This means that f has the same myThreadId it would have without the timeout wrapper. Any exceptions f might throw cancel the timeout and propagate further up. It also possible for f to receive exceptions thrown to it by another thread." They implement this by executing the action in the current thread. Yours executes the action in another thread. regards, Bas [1] http://haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Control-Concu...

On Tue, Mar 23, 2010 at 1:02 PM, Bas van Dijk
On Tue, Mar 23, 2010 at 8:23 PM, David Leimbach
wrote: Is this just a problem of spawning too many forkIO resources that never produce a result?
It looks like it. Lets look at the implementation of timeout:
timeout :: Int -> IO a -> IO (Maybe a) timeout n f | n < 0 = fmap Just f | n == 0 = return Nothing | otherwise = do pid <- myThreadId ex <- fmap Timeout newUnique handleJust (\e -> if e == ex then Just () else Nothing) (\_ -> return Nothing) (bracket (forkIO (threadDelay n >> throwTo pid ex)) (killThread) (\_ -> fmap Just f))
We see a thread is forked that throws the Timeout exception to the current thread after n microseconds. However when the current thread finishes early this timeout thread will be killed. I assume that when a thread is killed it can be garbage collected. (However we have to watch out for [1]) So it's a big surprise to me that we're seeing this space-leak!
Maybe you can file a bug report?
Seems like I should
I was thinking of trying something like the following in System.Timeout's place:
module Main where import Control.Concurrent.MVar import Control.Concurrent import Data.Maybe
timeout :: Int -> IO a -> IO (Maybe a) timeout time action = do someMVar <- newEmptyMVar -- MVar is a Maybe timeoutThread <- forkIO $ nothingIzer time someMVar forkIO $ actionRunner action someMVar timeoutThread takeMVar someMVar >>= return where nothingIzer time mvar = threadDelay time >> putMVar mvar Nothing actionRunner action mvar timeoutThread = do res <- action killThread timeoutThread putMVar mvar $ Just res main :: IO () main = do res <- timeout (5 * 10 ^ 6) (getLine >>= putStrLn) case res of Nothing -> putStrLn "Timeout" Just x -> putStrLn "Success"
The original timeout obeys the following specification:
"The design of this combinator was guided by the objective that timeout n f should behave exactly the same as f as long as f doesn't time out. This means that f has the same myThreadId it would have without the timeout wrapper. Any exceptions f might throw cancel the timeout and propagate further up. It also possible for f to receive exceptions thrown to it by another thread."
They implement this by executing the action in the current thread. Yours executes the action in another thread.
True, but mine's not leaking space! ;-) I think I can fix the action running in the other thread issue.
regards,
Bas
[1] http://haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Control-Concu...

On Tue, Mar 23, 2010 at 1:06 PM, David Leimbach
On Tue, Mar 23, 2010 at 1:02 PM, Bas van Dijk
wrote: On Tue, Mar 23, 2010 at 8:23 PM, David Leimbach
wrote: Is this just a problem of spawning too many forkIO resources that never produce a result?
It looks like it. Lets look at the implementation of timeout:
timeout :: Int -> IO a -> IO (Maybe a) timeout n f | n < 0 = fmap Just f | n == 0 = return Nothing | otherwise = do pid <- myThreadId ex <- fmap Timeout newUnique handleJust (\e -> if e == ex then Just () else Nothing) (\_ -> return Nothing) (bracket (forkIO (threadDelay n >> throwTo pid ex)) (killThread) (\_ -> fmap Just f))
We see a thread is forked that throws the Timeout exception to the current thread after n microseconds. However when the current thread finishes early this timeout thread will be killed. I assume that when a thread is killed it can be garbage collected. (However we have to watch out for [1]) So it's a big surprise to me that we're seeing this space-leak!
Maybe you can file a bug report?
Seems like I should
I was thinking of trying something like the following in System.Timeout's place:
module Main where import Control.Concurrent.MVar import Control.Concurrent import Data.Maybe
timeout :: Int -> IO a -> IO (Maybe a) timeout time action = do someMVar <- newEmptyMVar -- MVar is a Maybe timeoutThread <- forkIO $ nothingIzer time someMVar forkIO $ actionRunner action someMVar timeoutThread takeMVar someMVar >>= return where nothingIzer time mvar = threadDelay time >> putMVar mvar Nothing actionRunner action mvar timeoutThread = do res <- action killThread timeoutThread putMVar mvar $ Just res main :: IO () main = do res <- timeout (5 * 10 ^ 6) (getLine >>= putStrLn) case res of Nothing -> putStrLn "Timeout" Just x -> putStrLn "Success"
The original timeout obeys the following specification:
"The design of this combinator was guided by the objective that timeout n f should behave exactly the same as f as long as f doesn't time out. This means that f has the same myThreadId it would have without the timeout wrapper. Any exceptions f might throw cancel the timeout and propagate further up. It also possible for f to receive exceptions thrown to it by another thread."
They implement this by executing the action in the current thread. Yours executes the action in another thread.
True, but mine's not leaking space! ;-) I think I can fix the action running in the other thread issue.
Ok, that's a lot trickier than it looks, but you're still right; I don't expect the space leak either. What I did do was throw any exception caught in the "actionThread" back to the main thread to try to get it as close as I can to running in the main thread to begin with. I'll go ahead and file a bug, just as soon as I figure out where/how :-) Dave
regards,
Bas
[1] http://haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Control-Concu...

On 23/03/10 17:40, David Leimbach wrote:
Trying to understand why the code here: http://moonpatio.com/fastcgi/hpaste.fcgi/view?id=8823#a8823 exhausts memory.
I need to have timeouts in a program I'm writing that will run an interactive polling session of some remote resources, and know when to give up and handle that error. Unfortunately this code dies pretty quickly and produces an -hc graph like the one attached.
It seems that System.Timeout can't be used for this. I should note that if the code is changed to use an inifnite timeout (-1) that this problem doesn't occur. Is this a bug in System.Timeout, or is there something I should be doing to keep the data size down?
The leak is caused by the Data.Unique library, and coincidentally it was fixed recently. 6.12.2 will have the fix. Cheers, Simon

On Tue, Mar 23, 2010 at 10:20 PM, Simon Marlow
The leak is caused by the Data.Unique library, and coincidentally it was fixed recently. 6.12.2 will have the fix.
Oh yes of course, I've reported that bug myself but didn't realize it was the problem here :-) David, to clarify the problem: newUnqiue is currently implemented as: newUnique :: IO Unique newUnique = do val <- takeMVar uniqSource let next = val+1 putMVar uniqSource next return (Unique next) You can see that the 'next' value is lazily written to the uniqSource MVar. When you repeatedly call newUnique (like in your example) a big thunk is build up: 1+1+1+...+1 which causes the space-leak. In the recent fix, 'next' is strictly evaluated before it is written to the MVar which prevents a big thunk to build up. regards, Bas

On Tue, Mar 23, 2010 at 4:04 PM, Bas van Dijk
On Tue, Mar 23, 2010 at 10:20 PM, Simon Marlow
wrote: The leak is caused by the Data.Unique library, and coincidentally it was fixed recently. 6.12.2 will have the fix.
Oh yes of course, I've reported that bug myself but didn't realize it was the problem here :-)
David, to clarify the problem: newUnqiue is currently implemented as:
newUnique :: IO Unique newUnique = do val <- takeMVar uniqSource let next = val+1 putMVar uniqSource next return (Unique next)
You can see that the 'next' value is lazily written to the uniqSource MVar. When you repeatedly call newUnique (like in your example) a big thunk is build up: 1+1+1+...+1 which causes the space-leak. In the recent fix, 'next' is strictly evaluated before it is written to the MVar which prevents a big thunk to build up.
regards,
Bas
Thanks for this excellent description of what's going on. This whole thread has been a reminder of what makes the Haskell community truly excellent to work with. I appreciate everything you guys are doing! Dave
participants (4)
-
Bas van Dijk
-
David Leimbach
-
Roel van Dijk
-
Simon Marlow