New Bound Threads Proposal
Wolfgang Thaller
wolfgang.thaller at gmx.net
Tue May 6 09:19:17 EDT 2003
> Thus motivated, I've sketched Proposal 4, which is a sort of
> combinatory
> of P2 and P3. Much simpler than P2, but addressing the concerns
> Wolfgang raises.
>
> The main difference relative to P3 is that a Haskell thread is
> either unbound
> or bound to a native thread N
>
> Like P2, it has the property that at most one Haskell thread can be
> bound to a native thread N. Also like P1 and P2, the unbound Haskell
> threads can be executed one-per-native-thread, or by a pool of worker
> native threads, as you please.
>
> Unlike P2, there is no notion of an "associated" native thread, or of
> "temporary binding" of a Haskell thread to a native thread.
>
> Details in CVS, and in a Postscript file that I'll send separately (I'm
> having trouble with my externally-visible web site).
>
> Wolfgang, does this help?
Yes, it definitely helps. It seems to be equivalent to "P1, but all
foreign exports are bound".
Some remarks:
*) forkOS needn't be a primitive, it can be implemented via the FFI (cf
Section 3.2, first Proposal).
*) The semantics should probably have an (END) rule that specifies that
a thread created using forkIO can just end (without returning anywhere).
*) We should perhaps add a primitive for querying whether the current
thread is bound or not.
This can be used for writing combinators that use forkOS only when
necessary to make sure that we can access a foreign API that uses
thread-local state.
*) I don't think that a bindToOS primitive is really necessary,
emulating it using forkIO shouldn't be noticably slower, IMO.
*) We might sacrifice a little performance by making all foreign
exports "bound". That should be paid back in simplicity. Hardcore
hackers can always use forkIO to move work to a lightweight thread.
One issue remains however (and that's the topic of the rest of this
e-mail); what to do about broken libraries that treat the "main" OS
thread (i.e. the one that static initializers are run in) as special?
This really happens; in fact both of Apple's GUI APIs are that
brain-dead in the current version of Mac OS X.
In P2, that was the reason for "associating" the "main" Haskell thread
to the "main" IO thread. The costs for that are negligible in P2, but
_binding_ the "main" Haskell thread to the "main" OS thread might be
overkill (or it might not be, see below).
If we don't bind the main thread, we will need some other way to get
access to it:
For the GHC implementation, it would probably be possible to "trick"
the implementation into using the "main" OS thread using something like
this:
main = main'
foreigh import "foo" main' :: IO ()
foreign export "foo" main'' :: IO ()
main'' = ...
_IF_ the implementation behaves the way I think the GHC implementation
will, then main'' will be bound to the "main" OS thread. (The FFI
business could of course be put in a combinator useMainOSThread or
something).
But that doesn't necessarily work for all implementations, so perhaps
we'd have to add it to the semantics somehow...
Now if we do bind the main thread, what are the costs?
If we had
main = forkIO doLongComputation >> doAnotherLongComputation
there'd be OS thread switching going on. To optimize that, we'd have to
write
main = do
forkIO doLongComputation
mv <- newEmptyMVar
forIO (doAnotherLongComputation >> putMVar mv ())
takeMVar mv
... so that there'd be no OS thread switching.
So, our options seem to be
1) bind the "main" Haskell thread to the "main" OS thread
2) don't bind the "main" Haskell thread to the "main" OS thread
2a) complicate the system by adding a way to access the "main" OS
thread
2b) keep the system simple, use the hack I described above for GHC
programs that use Apple's libraries, and hope that Apple fixes it's
libraries before people want to use them with other implementations of
proposal4 where the hack doesn't work.
OK, that's all..
Cheers,
Wolfgang
More information about the FFI
mailing list