[Haskell-cafe] Re: [reactive] problem with unamb -- doesn't kill
enough threads
Simon Marlow
marlowsd at gmail.com
Fri Dec 19 04:48:33 EST 2008
Sounds like you should use an exception handler so that when the parent
dies it also kills its children. Be very careful with race conditions ;-)
For a good example of how to do this sort of thing, see
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Timeout.html
the docs are sadly missing the source links at the moment, I'm not sure
why, but you can find the source in
http://darcs.haskell.org/packages/base/System/Timeout.hs
Cheers,
Simon
Conal Elliott wrote:
> (I'm broadening the discussion to include haskell-cafe.)
>
> Andy -- What do you mean by "handling all thread forking locally"?
>
> - Conal
>
> On Thu, Dec 18, 2008 at 1:57 PM, Andy Gill <andygill at ku.edu
> <mailto:andygill at ku.edu>> wrote:
>
> Conal, et. al,
>
> I was looking for exactly this about 6~9 months ago. I got the
> suggestion to pose it as a challenge
> to the community by Duncan Coutts. What you need is thread groups,
> where for a ThreadId, you can send a signal
> to all its children, even missing generations if needed.
>
> I know of no way to fix this at the Haskell level without handling
> all thread forking locally.
>
> Perhaps a ICFP paper about the pending implementation :-) but I'm
> not sure about the research content here.
>
> Again, there is something deep about values with lifetimes.
>
> Andy Gill
>
>
> On Dec 18, 2008, at 3: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 <mailto:Reactive at haskell.org>
>> http://www.haskell.org/mailman/listinfo/reactive
>
>
>
> ------------------------------------------------------------------------
>
> _______________________________________________
> 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