Interruptible threads with IO loops

Hello. I'm trying to get some threads that I can stop and get last values that was computed (and that values are IO values, in fact). Here is my first approach: module Main where import Control.Concurrent (MVar, threadDelay, forkIO, newMVar, putMVar, readMVar) tick :: Int -> IO Int tick v = return $ v + 1 loop :: MVar Bool -> a -> (a -> IO a) -> IO a loop var init loopfun = do next <- loopfun init shouldStop <- readMVar var case shouldStop of True -> return next False -> loop var next loopfun runLoop :: Int -> IO () runLoop timeout = do var <- newMVar False forkIO $ threadDelay timeout >> putMVar var True value <- loop var 0 tick print value main :: IO () main = runLoop 30000000 The problem is that it looks a little messy and what's worse it leaks memory. So I'm wondering if there is a better approach to do so or some fix to memory leak.

Suggestion: use an IORef and asynchronous exceptions, see below for
untested code.
On Wed, Dec 21, 2011 at 6:52 AM, Fedor Gogolev
Hello. I'm trying to get some threads that I can stop and get last values that was computed (and that values are IO values, in fact). Here is my first approach:
module Main where
import Control.Concurrent (MVar, threadDelay, forkIO, newMVar, putMVar, readMVar)
tick :: Int -> IO Int tick v = return $ v + 1
loop :: MVar Bool -> a -> (a -> IO a) -> IO a loop var init loopfun = do next <- loopfun init shouldStop <- readMVar var case shouldStop of True -> return next False -> loop var next loopfun
loop :: IORef a -> (a -> IO a) -> IO () loop var loopfun = readIORef var >>= go where go val = do next <- loopfun val writeIORef var next go next
runLoop :: Int -> IO () runLoop timeout = do var <- newMVar False forkIO $ threadDelay timeout >> putMVar var True value <- loop var 0 tick print value
runLoop timeout = do var <- newIORef 0 lock <- newEmptyMVar loopTid <- forkIO $ loop var tick >> putMVar lock () delayTid <- forkIO $ threadDelay timeout >> killThread loopTid >> putMVar lock () takeMVar lock killThread delayTid value <- readIORef var print value
main :: IO () main = runLoop 30000000
The problem is that it looks a little messy and what's worse it leaks memory. So I'm wondering if there is a better approach to do so or some fix to memory leak.
Again, code above is untested and was written on my e-mail client =). But the idea seems fine. Cheers, -- Felipe.

On Dec 21, 2011, at 6:52 PM, Fedor Gogolev wrote:
Hello. I'm trying to get some threads that I can stop and get last values that was computed (and that values are IO values, in fact). Here is my first approach: [...] tick :: Int -> IO Int tick v = return $ v + 1 [...] The problem is that it looks a little messy and what's worse it leaks memory. So I'm wondering if there is a better approach to do so or some fix to memory leak.
I don't have any tips for cleaning up the code off the top of my head, but I suspect that the memory leak is coming from the fact that the expression (v+1) is not being forced, which means that each iteration of the loop is constructing a new thunk with a reference to the old thunk resulting in a data structure that is growing in memory usage over time. In this case the fix is easy: just replace "return" in "tick" with "evaluate" from Control.Exception, since "evaluate" guarantees in this case that the expression will be evaluated before being returned. (Caveat: What I said about "evaluate" will be true for numeric expressions, but for non-trivial data structures "evaluate" only ensures that the expression is evaluated to something called weak-head normal form, which essentially means that it will only evaluate enough of the expression to figure out what the outermost constructor of the datatype is; it just so happens that for numeric expressions the outermost data constructor is enough to give you the numeric value.) Cheers, Greg

Hi, Am Mittwoch, den 21.12.2011, 19:15 +1000 schrieb Gregory Crosswhite:
I don't have any tips for cleaning up the code off the top of my head, but I suspect that the memory leak is coming from the fact that the expression (v+1) is not being forced, which means that each iteration of the loop is constructing a new thunk with a reference to the old thunk resulting in a data structure that is growing in memory usage over time.
this problem comes up in various places; forcing the whole thunk is of course an option, but would it be possible – theoretical, with the GHC runtime, or even with current tools – to have a function evaluateUntilItDoesNotNeed :: a -> b -> a such that f x `evaluateUntilItDoesNotNeed` x will not retain a reference to x, but is otherwise as lazy as possible? If thunks retain references to their free variables, and these can be introspected, then it should be possible to keep seq’ing those thunks that refer to x, until the expression is either fully evaluated or no referenced thunk references x. This would be particularly handy when with, for example snd tuple `evaluateUntilItDoesNotNeed` tuple where the tuple is unevaluated in the right component (and where we don’t want to force this just now), but retains something large in the left component (that we want to become GCable). Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

On Wed, Dec 21, 2011 at 7:31 AM, Joachim Breitner
this problem comes up in various places; forcing the whole thunk is of course an option, but would it be possible – theoretical, with the GHC runtime, or even with current tools – to have a function evaluateUntilItDoesNotNeed :: a -> b -> a such that f x `evaluateUntilItDoesNotNeed` x will not retain a reference to x, but is otherwise as lazy as possible?
If thunks retain references to their free variables, and these can be introspected, then it should be possible to keep seq’ing those thunks that refer to x, until the expression is either fully evaluated or no referenced thunk references x.
Sounds complicated. What about map f xs `evaluateUntilItDoesNotNeed` xs If it evaluated only the head of 'map f xs' then the result would not depend on 'xs' anymore, but it would depend on the tail of 'xs'. Cheers, -- Felipe.

On 12/21/11 4:31 AM, Joachim Breitner wrote:
This would be particularly handy when with, for example snd tuple `evaluateUntilItDoesNotNeed` tuple where the tuple is unevaluated in the right component (and where we don’t want to force this just now), but retains something large in the left component (that we want to become GCable).
Can't you already do that with: let (_,x) = tuple in ...x... or case tuple of (_,x) -> ...x... ? The tuple will be evaluated far enough that we can access its second component, and then we're free to discard the tuple itself provided it's not referenced elsewhere. The above would only be strict in x if the use sites are strict. Or do you mean that you want something with the semantics of the above, but with a syntactic form that enables us to abstract out the ellipses? -- Live well, ~wren

Dear Wren, Am Mittwoch, den 21.12.2011, 13:04 -0500 schrieb wren ng thornton:
On 12/21/11 4:31 AM, Joachim Breitner wrote:
This would be particularly handy when with, for example snd tuple `evaluateUntilItDoesNotNeed` tuple where the tuple is unevaluated in the right component (and where we don’t want to force this just now), but retains something large in the left component (that we want to become GCable).
Can't you already do that with:
let (_,x) = tuple in ...x...
or
case tuple of (_,x) -> ...x...
?
The tuple will be evaluated far enough that we can access its second component, and then we're free to discard the tuple itself provided it's not referenced elsewhere. The above would only be strict in x if the use sites are strict.
Or do you mean that you want something with the semantics of the above, but with a syntactic form that enables us to abstract out the ellipses?
Your first example would not work, because the tuple is only evaluated when x is evaluated, which might be later than the point where I want the left component of the tuple to be GCed: Prelude Debug.Trace> let (_,x) = trace "some tuple" (error "a", error "b") in const () x () The second case works in this particular instance: Prelude Debug.Trace> case trace "some tuple" (error "a", error "b") of (_,x) -> const () x some tuple () But assume the function is not snd but rather a library provided function that you have no control over and that you know returns one component of the tuple, but you don’t know which (depending on other parameters, perhaps). The advantage of a `evaluateUntilItDoesNotNeed` would be that it can be combined with code that was written without having such considerations in mind. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

On 21 December 2011 09:52, Fedor Gogolev
I'm trying to get some threads that I can stop and get last values that was computed (and that values are IO values, in fact).
I'm not sure it's what you need but you might want to look at: http://hackage.haskell.org/package/Workflow Bas
participants (6)
-
Bas van Dijk
-
Fedor Gogolev
-
Felipe Almeida Lessa
-
Gregory Crosswhite
-
Joachim Breitner
-
wren ng thornton