Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Bas van Dijk
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-Concurrent.html#11

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 mmi...@gmail.com wrote:
 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Mitar
Hi!

On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk v.dijk@gmail.com 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.

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Gregory Collins
Mitar mmi...@gmail.com writes:

 Hi!

 On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk v.dijk@gmail.com 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 g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread 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!

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
g...@gregorycollins.net wrote:
 Mitar mmi...@gmail.com writes:

 Hi!

 On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk v.dijk@gmail.com 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 g...@gregorycollins.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Gregory Collins
Bas van Dijk v.dijk@gmail.com 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 g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Bas van Dijk
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
g...@gregorycollins.net wrote:
 Bas van Dijk v.dijk@gmail.com 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 g...@gregorycollins.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe