[Haskell-cafe] Cleaning up threads
Bas van Dijk
v.dijk.bas at gmail.com
Tue Sep 14 17:46:51 EDT 2010
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 <mmitar at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list