[reactive] problem with unamb -- doesn't kill enough threads
Sterling Clover
s.clover at gmail.com
Thu Dec 18 23:38:47 EST 2008
Using `finally` here would seem like the wrong thing to me, since you
don't want to `finally` kill subthreads, but only to kill them if you
yourself are killed. Note that finally also only cleans up if
interrupted *during* the computation of the first part -- it doesn't
attach a handler to the thread as a whole.
The best I can think of at the moment is (in pseudocode, and probably
not handling some corner cases)
withSafeFork :: (IO () -> IO ThreadId) -> IO a) -> IO a
{-
withSafeFork $ \safeFork -> do
safeFork something
safeFork somethingelse
-}
withSafeFork act = do
forkCleanup <- newMVar []
let safeFork x = withMVar forkCleanup $ \list -> do
tid <- forkIO x
return (tid, tid:list)
act safeFork `catchJustThreadKilled` const ((mapM_ (forkIO .
killThread) =<< readMVar forkCleanup) >>
rethrowThreadKilled)
The unthoughthrough bit here being what happens when you catch a
threadkilled in the middle of a safeFork call (at the moment, I
suspect, deadlock)... but that should be easy to work out.
The way to use this of course would be to hide forkIO and only allow
forking through withSafeFork.
Regards,
Sterl.
On Dec 18, 2008, at 4:43 PM, Conal Elliott wrote:
> I realized in the shower this morning that there's a serious flaw
> in my unamb implementation as described in http://conal.net/blog/
> posts/functional-concurrency-with-unambiguous-choice. I'm looking
> for ideas for fixing the flaw. Here's the code for racing
> computations:
>
> race :: IO a -> IO a -> IO a
> a `race` b = do v <- newEmptyMVar
> ta <- forkPut a v
> tb <- forkPut b v
> x <- takeMVar v
> killThread ta
> killThread tb
> return x
>
> forkPut :: IO a -> MVar a -> IO ThreadId
> forkPut act v = forkIO ((act >>= putMVar v) `catch` uhandler
> `catch` bhandler)
> where
> uhandler (ErrorCall "Prelude.undefined") = return ()
> uhandler err = throw err
> bhandler BlockedOnDeadMVar = return ()
>
> The problem is that each of the threads ta and tb may have spawned
> other threads, directly or indirectly. When I kill them, they
> don't get a chance to kill their sub-threads.
>
> Perhaps I want some form of garbage collection of threads, perhaps
> akin to Henry Baker's paper "The Incremental Garbage Collection of
> Processes". As with memory GC, dropping one consumer would
> sometimes result is cascading de-allocations. That cascade is
> missing from my implementation.
>
> Or maybe there's a simple and dependable manual solution, enhancing
> the method above.
>
> Any ideas?
>
> - Conal
>
>
> _______________________________________________
> Reactive mailing list
> Reactive at haskell.org
> http://www.haskell.org/mailman/listinfo/reactive
More information about the Reactive
mailing list