
Hi! I run multiple threads where I would like that exception from any of them (and main) propagate to others but at the same time that they can gracefully cleanup after themselves (even if this means not exiting). I have this code to try, but cleanup functions (stop) are interrupted. How can I improve this code so that this not happen? module Test where import Control.Concurrent import Control.Exception import Control.Monad thread :: String -> IO ThreadId thread name = do mainThread <- myThreadId forkIO $ handle (throwTo mainThread :: SomeException -> IO ()) $ -- I want that possible exception in start, stop or run is propagated to the main thread so that all other threads are cleaned up bracket_ start stop run where start = putStrLn $ name ++ " started" stop = forever $ putStrLn $ name ++ " stopped" -- I want that all threads have as much time as they need to cleanup after themselves (closing (IO) resources and similar), even if this means not dying run = forever $ threadDelay $ 10 * 1000 * 1000 run :: IO () run = do threadDelay $ 1000 * 1000 fail "exit" main :: IO () main = do bracket (thread "foo") killThread $ \_ -> bracket (thread "bar") killThread $ \_ -> bracket (thread "baz") killThread (\_ -> run) Mitar

Mitar
I run multiple threads where I would like that exception from any of them (and main) propagate to others but at the same time that they can gracefully cleanup after themselves (even if this means not exiting). I have this code to try, but cleanup functions (stop) are interrupted. How can I improve this code so that this not happen?
In general it's better to avoid using killThread. There are much cleaner ways to tell a thread to exit. A very common piece of code found in my applications is this: data StateCmd s = GetState (s -> IO ()) | ModifyState (s -> s) | Quit (() -> IO ()) | SetState s stateThread :: s -> IO (StateCmd s -> IO ()) stateThread initialState = do cmdVar <- newEmptyMVar forkIO . runContT return . fmap fst . runStateT initialState . forever $ do cmd <- inBase $ takeMVar cmdVar case cmd of GetState c -> get >>= inBase . c ModifyState f -> sets_ f Quit c -> inBase (c ()) >> abort () SetState x -> set x return (putMVar cmdVar) askThread :: (c -> IO ()) -> ((r -> IO ()) -> c) -> IO r askThread sendCmd cmdName = do result <- newEmptyMVar sendCmd $ cmdName (putMVar result) takeMVar result The 'stateThread' function gives a computation, which starts a thread to maintain state of a certain type. It returns a function to send commands to this thread. Those commands, which don't require an answer like SetState and ModifyState, can be sent right away using this command. For those, which will give an answer like GetState and Quit, exists a convenience function askThread. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Excerpts from Ertugrul Soeylemez's message of Mon Sep 13 03:03:11 -0400 2010:
In general it's better to avoid using killThread. There are much cleaner ways to tell a thread to exit.
This advice doesn't really apply to Haskell: in fact, the GHC developers have thought really carefully about this: http://research.microsoft.com/en-us/um/people/simonpj/papers/asynch-exns.ps.... Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions. Edward

On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang
Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions.
Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong.

Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong.
Does this apply to pure code? I use threads to gradually force some data, if it turns out the data won't be needed the threads are killed. I've never had a disaster because of it.

"Bryan O'Sullivan"
On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang
wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions.
Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong.
That's surprising to me -- this is how we kill the Snap webserver
(killThread the controlling thread...).
G
--
Gregory Collins

On Tue, Sep 14, 2010 at 12:04 PM, Gregory Collins
That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...).
It's one thing to design code to work that way and test it all the time, but it would be quite another to claim that killThread makes sense outside of that very narrow context.

Hi!
On Tue, Sep 14, 2010 at 9:04 PM, Gregory Collins
That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...).
Yes. This does work. The only problem is that my main thread then kills child threads, which then start killing main thread again, which then again kills child threads and interrupt cleanup. Probably it can be solved with mask: http://hackage.haskell.org/trac/ghc/ticket/1036 My question is if there is some good code example how to achieve that before mask is available. The code I wrote in my original post does not work as intended. Mitar

On Tue, Sep 14, 2010 at 9:44 PM, Mitar
Hi!
On Tue, Sep 14, 2010 at 9:04 PM, Gregory Collins
wrote: That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...).
Yes. This does work. The only problem is that my main thread then kills child threads, which then start killing main thread again, which then again kills child threads and interrupt cleanup.
This sounds wrong. Why is the main thread sending more than one kill? Handlers for some exception shouldn't run more than once unless you set them up that way. Are you perhaps being tripped up by the issue whereby when the main thread dies, the RTS just shuts down even if other threads are running? You might find you need some kind of maybe MVar-driven mechanism to keep the main thread alive until all else is definitely dead. Maybe this behaviour should be considered a bug, I don't know. It would be nice if after a forkIO threads were effectively equal.

On Tue, Sep 14, 2010 at 11:29 AM, Bryan O'Sullivan
On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang
wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions.
Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong.
I don't use killThread, and I write what I'd call somewhat complex concurrent Haskell software for a living right now :-). Instead I have a TChan of commands that I can send to a thread, either from the outside or inside, and that thread will eventually come back to it's event loop that looks at such messages, and shut down gracefully from there. Of course the only time this would happen is if something goes wrong and I'm going to restart and forget all the data I have accumulated thus far anyway.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 14/09/10 19:29, Bryan O'Sullivan wrote:
On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang
mailto:ezyang@mit.edu> wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions.
Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong.
Avoiding killThread on its own doesn't help: Control-C sends an asynchronous exception to the main thread, and a stack overflow also results in an asynchronous exception. So for now to completely avoid asynchronous exceptions you'd need to catch Control-C, and disable the stack limit (+RTS -K1000G). I expect we'll map other fatal signals to exceptions in the future (pending redesign of the signal API means we haven't got to that yet). So rather than admitting defeat here I'd like to see it become the norm to write async-exception-safe code. It's not that hard, especially with the new mask API coming in GHC 7.0. Asynchronous exceptions are a major selling point of Haskell, we should make more noise about them! Being able to sanely handle Control-C, and the fact that a large fraction of code is async-exception-safe by construction (because it isn't in the IO monad), are big wins. Cheers, Simon

Hi!
On Tue, Sep 21, 2010 at 11:10 PM, Simon Marlow
So rather than admitting defeat here I'd like to see it become the norm to write async-exception-safe code.
This is also what I think. You have to make your code work with exceptions, because they will come sooner or later. So if you handle them properly, once you have this implemented, then you can easily use them also for your own stuff.
It's not that hard, especially with the new mask API coming in GHC 7.0.
Not hard? I see it almost impossible without mask. You cannot have arbitrary long cleanup functions in for example bracket because somebody can (and will) interrupt it even if you block, because some function somewhere deep bellow will unblock. And there is no way to resume after exception in Haskell. What would I also like to see in Haskell is that it would be somehow possible to see which all exceptions could your function (through used functions there) throw. In this way it would be really possible to make async-exception-safe functions (as we really do not want catch-all all around). (Of course the problem with this approach is if somebody changes underlying function it could get additional possible exception(s) to be thrown.) So it would be even better if this would be solved like pattern matching warning (so you could see if you are missing some exception through warning) or even better: that type system would enforce you to or catch or declare throwing/passing exception yourself. Similar how Java has. Because one other major Haskell's selling point is that you (are said to) know from type if and which side-effects a function has. This is the story behind IO monad. And with exceptions you do not have this information anymore. I believe this should be visible through type system. Something like: http://paczesiowa.blogspot.com/2010/01/pure-extensible-exceptions-and-self.h... ? Mitar

[Apologies to subscribers of haskell@haskell.org, where this message already appeared, but it was suggested that haskell-cafe might be a better place to reach potential applicants.] The Stanford Secure Computer Systems research group seeks an experienced Haskell programmer to participate in research on secure, robust software systems. The primary responsibility will be to collaborate closely with other researchers in building a Haskell web framework that achieves security through a novel approach to dynamic information flow control. The job will provide access to Stanford's world-leading Computer Science faculty and students; it will furthermore allow considerable freedom to pursue other collaborations and side projects that advance the state of the art in host security and produce scientific publications. To maximize impact, software developed as part of these efforts will be released under a free-software license; moreover, duties may include developing documentation or educational materials that promote adoption of the research output or of Haskell in general. The position requires significant Haskell expertise, including knowledge of the Glasgow Haskell Compiler (ghc), optimization pragmas, the foreign function interface, debugging, and performance-tuning. In addition, while not required, any of the following qualifications will be helpful and should be highlighted in applications: - Experience publishing or maintaining a package on hackage. - Experience programming in C. - Knowledge of web programming and JavaScript. - A broad understanding of operating systems and networking concepts. - A Ph.D. in Computer Science. - Previous research or peer-reviewed publications. This is a two-year fixed-term position with the possibility of extension. While the position can potentially become permanent, we also welcome applicants who view it as a stepping stone to a research or faculty career elsewhere or to a start-up company. The faculty members involved in this project have a track record of placing students, staff, and post-doctoral researchers at prestigious institutions and will provide a level of mentoring appropriate to the successful candidate's qualifications and ambitions. Note that Stanford can sponsor visas for foreign nationals when necessary. For questions about this position, please email Prof. David Mazieres from the following web page: http://www.scs.stanford.edu/~dm/addr/ To apply for this position: - Go to http://jobs.stanford.edu/find_a_job.html - Enter 40012 in the Keyword Search box. - Click on the job listing link. - Scroll down to the bottom and click on "Apply" to upload a resume and cover letter. Or access the on-line job posting from this URL: https://recruit.trovix.com/jobhostmaster/jobhost/ViewJobPostDetails.do?jobPostId=njxfd6fgqncgpaggoswjfy22bd&accountId=de85ad313f8598db1c42b567a3df24a00497ba22&button=&action=viewDetails Or apply directly at the following link: http://jobs.stanford.edu/find_a_job.html?accountId=de85ad313f8598db1c42b567a3df24a00497ba22&jobPostId=njxfd6fgqncgpaggoswjfy22bd&action=applyToJobEmail

On Wed, Sep 22, 2010 at 3:18 AM, Mitar
What would I also like to see in Haskell is that it would be somehow possible to see which all exceptions could your function (through used functions there) throw. In this way it would be really possible to make async-exception-safe functions (as we really do not want catch-all all around). (Of course the problem with this approach is if somebody changes underlying function it could get additional possible exception(s) to be thrown.)
So it would be even better if this would be solved like pattern matching warning (so you could see if you are missing some exception through warning) or even better: that type system would enforce you to or catch or declare throwing/passing exception yourself. Similar how Java has.
Because one other major Haskell's selling point is that you (are said to) know from type if and which side-effects a function has. This is the story behind IO monad. And with exceptions you do not have this information anymore. I believe this should be visible through type system.
Something like:
http://paczesiowa.blogspot.com/2010/01/pure-extensible-exceptions-and-self.h...
For type-safe _synchronous_ exception handling we have Pepe Iborra's: http://hackage.haskell.org/package/control-monad-exception However we don't have anything similar for asynchronous exception handling. What will a type-safe asynchronous exception handling API look like? What guarantees should it provide? Regards, Bas

On 22/09/2010 02:18, Mitar wrote:
Hi!
On Tue, Sep 21, 2010 at 11:10 PM, Simon Marlow
wrote: So rather than admitting defeat here I'd like to see it become the norm to write async-exception-safe code.
This is also what I think. You have to make your code work with exceptions, because they will come sooner or later. So if you handle them properly, once you have this implemented, then you can easily use them also for your own stuff.
It's not that hard, especially with the new mask API coming in GHC 7.0.
Not hard? I see it almost impossible without mask. You cannot have arbitrary long cleanup functions in for example bracket because somebody can (and will) interrupt it even if you block, because some function somewhere deep bellow will unblock.
mask doesn't save you from this, because a function in a library below you might perform an interruptible operation like takeMVar, and that operation could receive another asynchronous exception. You could use maskUninterruptible, but that's not a good solution either - if an operation during cleanup really does block, you'd like to be able to Control-C your way out. So the only way out of this hole is: don't write long cleanup code that needs to mask exceptions. Find another way to do it. Cheers, Simon

Hi!
On Wed, Sep 22, 2010 at 10:21 AM, Simon Marlow
You could use maskUninterruptible, but that's not a good solution either - if an operation during cleanup really does block, you'd like to be able to Control-C your way out.
So maybe this shows a need for maskUninterruptibleExcept (user exception for example).
So the only way out of this hole is: don't write long cleanup code that needs to mask exceptions. Find another way to do it.
There is sometimes no other way. For example if cleanup requires extensive IO with robot on the Mars. It takes time for communicating in each direction and while waiting for the response it is really not a great idea that robot on the Mars is left in undefined state because cleanup function has been interrupted half a way doing its thing. Of course the protocol would be probably just that you send a message like "I am going away for some time, please confirm" and you wait for confirmation. So in most cases it will be OK even if the you do not really wait for confirmation, but sometimes there will be no confirmation and you will have to retry or try something else (like raise an alarm). (The point of such protocol message is that robot does not consume power trying to reach you when you are not there.) But yes, in this case I will simply use maskUninterruptible and also user should be blocked/masked from interrupting the cleanup. (He/she still has kill signal if this is really really what he/she wants.) Haskell great type checking is a great tool and help in mission critical programs, there is just this hidden side effect (exceptions) possibility built-in in language which has yet to be polished. In my opinion. This could be mitigated with "resume" from exception. But this is only one part of the story I am trying to rise here. The other is that me, as an user of some library function, do not know and cannot know (yet) which exceptions this function can throw at me. I believe this is a major drawback. Code behavior should be transparent and types do help here. But (possibility of) exceptions are hidden. To be prepared for any exception (even those not yet defined at the time of writing) in code is sometimes a too hard requirement (you are writing about async-exception-saftiness). Especially because for some exceptions you could want some behavior and for some other. Maybe what I am arguing for is that currently (with mask) you cannot say "mask everything except". To answer Bas: I do not know how this should look like. I just know that I am missing Java's transparency what can be thrown and what not and its at-compile-time checking if you have covered all possibilities. Mitar P.S.: I am not really doing a remote control for Mars robot in Haskell, but it is not so much far off. Maybe it will even be there someday.

On 22/09/2010 09:51, Mitar wrote:
Hi!
On Wed, Sep 22, 2010 at 10:21 AM, Simon Marlow
wrote: You could use maskUninterruptible, but that's not a good solution either - if an operation during cleanup really does block, you'd like to be able to Control-C your way out.
So maybe this shows a need for maskUninterruptibleExcept (user exception for example).
So the only way out of this hole is: don't write long cleanup code that needs to mask exceptions. Find another way to do it.
There is sometimes no other way. For example if cleanup requires extensive IO with robot on the Mars. It takes time for communicating in each direction and while waiting for the response it is really not a great idea that robot on the Mars is left in undefined state because cleanup function has been interrupted half a way doing its thing. Of course the protocol would be probably just that you send a message like "I am going away for some time, please confirm" and you wait for confirmation. So in most cases it will be OK even if the you do not really wait for confirmation, but sometimes there will be no confirmation and you will have to retry or try something else (like raise an alarm). (The point of such protocol message is that robot does not consume power trying to reach you when you are not there.)
Instead of thinking of this as "cleanup code" that runs in an exception handler, rather the program that communicates with the rover would have a state in which it is "recovering". The exception handler moves the program into the recovery state, and then continues. During the recovery state you can mask exceptions if you like, but you can also catch exceptions and handle them as you would in any other state. The point I'm making here is that when cleanup code gets long and unweildy, it should become part of the main program logic rather than an exception handler.
But yes, in this case I will simply use maskUninterruptible and also user should be blocked/masked from interrupting the cleanup. (He/she still has kill signal if this is really really what he/she wants.)
Haskell great type checking is a great tool and help in mission critical programs, there is just this hidden side effect (exceptions) possibility built-in in language which has yet to be polished. In my opinion.
This could be mitigated with "resume" from exception.
exceptions with resumption aren't exceptions, they're signals. We can already do this in Haskell: you install a handler for the signal, and in the handler you decide whether to throw an exception to a thread or not.
But this is only one part of the story I am trying to rise here. The other is that me, as an user of some library function, do not know and cannot know (yet) which exceptions this function can throw at me. I believe this is a major drawback.
You're talking about synchronous exceptions, which are a different beast entirely. Wars have been waged about whether synchronous exceptions should show up in the types; IMO the Java folks lost here, and the general feeling is that the Java way was a poor choice (but it was hard to tell from the outset, they did it for the right reasons).
Maybe what I am arguing for is that currently (with mask) you cannot say "mask everything except".
Perhaps, although that's quite tricky to implement. Presumably you would have to supply a predicate (as a Haskell function), and the RTS would have to apply your predicate to the exception in order to decide whether to mask it or not. What if the predicate loops, or raises an exception itself? Cheers, Simon
To answer Bas: I do not know how this should look like. I just know that I am missing Java's transparency what can be thrown and what not and its at-compile-time checking if you have covered all possibilities.
Mitar
P.S.: I am not really doing a remote control for Mars robot in Haskell, but it is not so much far off. Maybe it will even be there someday.

"Edward Z. Yang"
Excerpts from Ertugrul Soeylemez's message of Mon Sep 13 03:03:11 -0400 2010:
In general it's better to avoid using killThread. There are much cleaner ways to tell a thread to exit.
This advice doesn't really apply to Haskell: in fact, the GHC developers have thought really carefully about this:
http://research.microsoft.com/en-us/um/people/simonpj/papers/asynch-exns.ps....
Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions that would handle normal IO exceptions.
The point is that killThread throws an exception. An exception is usually an error condition. My approach strictly separates an unexpected crash from an intended quit. After all an application exiting normally shouldn't be an exception (i.e. something unexpected). Also using the Quit command from my example you can actually wait for the thread to finish cleanup work. You can't do this with an exception. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Hi!
On Wed, Sep 15, 2010 at 2:16 AM, Ertugrul Soeylemez
The point is that killThread throws an exception. An exception is usually an error condition.
This is reasoning based on nomenclature. If exceptions were named "Signal" or "Interrupt"?
My approach strictly separates an unexpected crash from an intended quit.
For this you can have multiple types of exceptions, some which signify error condition and some which signify that user has "interrupted" a process and that process should gracefully (exceptionally) quit. I like exceptions because you can split main logic from "exceptional" logic (like user wants to prematurely stop the program). But you still want to clean up properly everything. Once you have this "exceptional" logic in place (and you should always have it as some exceptional things can always happen) why do not use it also for less exceptional things (because you have cleaner code then).
Also using the Quit command from my example you can actually wait for the thread to finish cleanup work. You can't do this with an exception.
You can. If you would have a proper way to mask them: http://hackage.haskell.org/trac/ghc/ticket/1036 Mitar

Mitar
On Wed, Sep 15, 2010 at 2:16 AM, Ertugrul Soeylemez
wrote: The point is that killThread throws an exception. An exception is usually an error condition.
This is reasoning based on nomenclature. If exceptions were named "Signal" or "Interrupt"?
My approach strictly separates an unexpected crash from an intended quit.
For this you can have multiple types of exceptions, some which signify error condition and some which signify that user has "interrupted" a process and that process should gracefully (exceptionally) quit.
I like exceptions because you can split main logic from "exceptional" logic (like user wants to prematurely stop the program). But you still want to clean up properly everything. Once you have this "exceptional" logic in place (and you should always have it as some exceptional things can always happen) why do not use it also for less exceptional things (because you have cleaner code then).
The problem with exceptions is that Haskell's type system doesn't really capture them. A function raising an exception is semantically equivalent to a function, which recurses forever. On the other hand a well-typed abortion using the ContT monad transformer /is/ captured by the type system and hence can be stated and type-checked explicitly. Exceptions are side effects in Haskell. That's why an exception is semantically equivalent to a crash, hence my wording.
Also using the Quit command from my example you can actually wait for the thread to finish cleanup work. You can't do this with an exception.
You can. If you would have a proper way to mask them:
Even if you could mask them exception throwing and catching is outside of Haskell's type system. They're still an IO side effect. And also there is nothing wrong with using ContT. It doesn't make the code any more complicated and very likely even less. See my example. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Note that killing the main thread will also kill all other threads. See:
http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-Concu...
You can use my threads library to wait on a child thread and possibly
re-raise an exception that was thrown in or to it:
http://hackage.haskell.org/package/threads
Regards,
Bas
On Mon, Sep 13, 2010 at 5:32 AM, Mitar
Hi!
I run multiple threads where I would like that exception from any of them (and main) propagate to others but at the same time that they can gracefully cleanup after themselves (even if this means not exiting). I have this code to try, but cleanup functions (stop) are interrupted. How can I improve this code so that this not happen?
module Test where
import Control.Concurrent import Control.Exception import Control.Monad
thread :: String -> IO ThreadId thread name = do mainThread <- myThreadId forkIO $ handle (throwTo mainThread :: SomeException -> IO ()) $ -- I want that possible exception in start, stop or run is propagated to the main thread so that all other threads are cleaned up bracket_ start stop run where start = putStrLn $ name ++ " started" stop = forever $ putStrLn $ name ++ " stopped" -- I want that all threads have as much time as they need to cleanup after themselves (closing (IO) resources and similar), even if this means not dying run = forever $ threadDelay $ 10 * 1000 * 1000
run :: IO () run = do threadDelay $ 1000 * 1000 fail "exit"
main :: IO () main = do bracket (thread "foo") killThread $ \_ -> bracket (thread "bar") killThread $ \_ -> bracket (thread "baz") killThread (\_ -> run)
Mitar _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi!
On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk
Note that killing the main thread will also kill all other threads. See:
Yes. But how does those other threads have time to cleanup is my question.
You can use my threads library to wait on a child thread and possibly re-raise an exception that was thrown in or to it:
Thanks. Will look into it. Mitar

Mitar
Hi!
On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk
wrote: Note that killing the main thread will also kill all other threads. See:
Yes. But how does those other threads have time to cleanup is my question.
What we do in Snap is this: the master thread has a catch handler which
catches the AsyncException generated by the call to killThread. When we
get this, we instruct any service loop threads to exit, and they all
wait for service threads to terminate (currently by sleep-polling a
connections table, which I should probably fix...). Then the master
thread exits by just returning.
Note that I think the "main thread being killed kills all threads" issue
can be circumvented by using a little gadget like this:
------------------------------------------------------------------------
someWorkToDo :: IO ()
someWorkToDo = someStuff `catch` cleanupHandler
main :: IO ()
main = do
mv <- newEmptyMVar
tid <- forkIO (someWorkToDo `finally` putMVar mv ())
-- wait on thread to finish; any exception here is probably an
-- AsyncException, so kill the someWorkToDo master thread
-- yourself and wait on the mvar again
takeMVar mv `catch` \(e::SomeException) -> do
killThread tid
takeMVar mv
------------------------------------------------------------------------
At least, this is what we do in our webserver, and it seems to work
fine -- users complain about the delay involved in our slow cleanup
handler when they ctrl-c the server. :)
G
--
Gregory Collins

Don't forget to block asynchronous exception _before_ you fork in:
tid <- forkIO (someWorkToDo `finally` putMVar mv ())
Otherwise an asynchronous exception might be thrown to the thread
_before_ the 'putMVar mv ()' exception handler is installed leaving
your main thread in a dead-lock!
You can use the threads library which correctly abstracts over this pattern:
http://hackage.haskell.org/package/threads
Regards,
Bas
On Wed, Sep 15, 2010 at 2:23 AM, Gregory Collins
Mitar
writes: Hi!
On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk
wrote: Note that killing the main thread will also kill all other threads. See:
Yes. But how does those other threads have time to cleanup is my question.
What we do in Snap is this: the master thread has a catch handler which catches the AsyncException generated by the call to killThread. When we get this, we instruct any service loop threads to exit, and they all wait for service threads to terminate (currently by sleep-polling a connections table, which I should probably fix...). Then the master thread exits by just returning.
Note that I think the "main thread being killed kills all threads" issue can be circumvented by using a little gadget like this:
------------------------------------------------------------------------ someWorkToDo :: IO () someWorkToDo = someStuff `catch` cleanupHandler
main :: IO () main = do mv <- newEmptyMVar tid <- forkIO (someWorkToDo `finally` putMVar mv ())
-- wait on thread to finish; any exception here is probably an -- AsyncException, so kill the someWorkToDo master thread -- yourself and wait on the mvar again
takeMVar mv `catch` \(e::SomeException) -> do killThread tid takeMVar mv ------------------------------------------------------------------------
At least, this is what we do in our webserver, and it seems to work fine -- users complain about the delay involved in our slow cleanup handler when they ctrl-c the server. :)
G -- Gregory Collins

Bas van Dijk
Don't forget to block asynchronous exception _before_ you fork in:
tid <- forkIO (someWorkToDo `finally` putMVar mv ())
Otherwise an asynchronous exception might be thrown to the thread _before_ the 'putMVar mv ()' exception handler is installed leaving your main thread in a dead-lock!
Good catch, thank you,
G
--
Gregory Collins

Also don't forget to unblock asynchronous exceptions inside
'someWorkToDo' otherwise you can't throw exceptions to the thread.
Note that 'finally' unblocks asynchronous exceptions but I consider
this a bug. In the upcoming base library this is fixed[1] but I would
advise to fix the code right now to not be surprised later.
Also note that the threads library correctly unblocks asynchronous
exceptions when necessary.
Regards,
Bas
[1] http://hackage.haskell.org/trac/ghc/ticket/4035
On Wed, Sep 15, 2010 at 7:38 AM, Gregory Collins
Bas van Dijk
writes: Don't forget to block asynchronous exception _before_ you fork in:
tid <- forkIO (someWorkToDo `finally` putMVar mv ())
Otherwise an asynchronous exception might be thrown to the thread _before_ the 'putMVar mv ()' exception handler is installed leaving your main thread in a dead-lock!
Good catch, thank you,
G -- Gregory Collins
participants (11)
-
Bas van Dijk
-
Ben Millwood
-
Bryan O'Sullivan
-
David Leimbach
-
David Mazieres
-
Edward Z. Yang
-
Ertugrul Soeylemez
-
Evan Laforge
-
Gregory Collins
-
Mitar
-
Simon Marlow