[Haskell-cafe] Re: FFI and callbacks

Simon Marlow simonmar at microsoft.com
Wed Jul 20 17:16:10 EDT 2005


On 20 July 2005 18:49, John Goerzen wrote:

> On 2005-07-20, Simon Marlow <simonmar at microsoft.com> wrote:
>> This paper might help shed some light:
>> 
>>  http://www.haskell.org/~simonmar/papers/conc-ffi.pdf
> 
> Forgot to reply to this.  *Very helpful* link, I had always wondered
> what the bound thread functions in Control.Concurrent were for :-)
> 
> So let me see if I understand this correctly.
> 
> Let's say that I have:
> 
>  * A program that uses multiple lightweight Haskell threads (all
>    started with plain forkIO calls)
> 
>  * An event-driven C library, not not thread-aware, with a blocking
>    main loop
> 
>  * GHC 6.4
> 
>  * My C calls all imported "safe".
> 
> Now then, if I understand this correctly, that a call to the C main
> loop will create a new bound OS thread, so it will not interrupt any
> other forkIO'd threads in Haskell.

Not necessarily a *bound* OS thread.  A bound thread is only created by
an in-call to Haskell.  An out-call may happen in a separate OS thread
if the foreign import is "safe", that is, another OS thread will
continue to run the remaining Haskell threads while the call is in
progress.

> However, if one of my Haskell-based callbacks creates new threads with
> forkIO, I could be in trouble; if they make any calls into C, a new
> bound OS thread would be created for them, and this could wind up
> causing trouble in C.  I would probably need some sort of "global
> MVar" to synchronize access into the C world.

Bingo.  This is why you need to make all your calls to the C library
from a single thread.

> I also have some follow-up questions after looking at the
> Control.Concurrent API:
> 
> 1. It seems that there is no function that says "block the current
> thread until the thread given by ThreadId dies"

You can do something like this with an exception handler and an MVar or
TVar:

   do died <- atomically $ newTVar False
      forkIO (later (atomically $ writeTVar died True) $ ...)

      let wait = atomically $ do b <- readTVar died
                                 when (not b) retry

   where later = flip finally

granted, it's hard to implement exactly what you were asking for.
Another way to do it would be to put a finalizer on the ThreadId, but
that would incur a delay until the GC discovered the thread was
unreachable.

Hmm, perhaps we should have

  threadIsAlive :: ThreadId -> STM Bool

> 2. What is the preferred way to implement a simple lock?  With an
> MVar? 

TVars are the way to go, although MVars do perform slightly better at
the moment (at least if you stick to the simple putMVar/takeMVar
operations).

Cheers,
	Simon


More information about the Haskell-Cafe mailing list