multithreading with multiprocessing (Was: Concurrent and Posix libraries...)

Dean Herington heringto@cs.unc.edu
Thu, 20 Dec 2001 10:47:13 -0500


`forkProcess` creates an exact copy of the calling process, except for the
return value from `forkProcess` that allows for discriminating the parent
from the child.  In your example, there are two active threads at the time
`forkProcess` is done, so the new process has (copies of) the same two
active threads.  Then the race is on in the new process: depending on the
(unspecified) order of execution, the copy of the initial thread may get
to the `print` before its sibling thread gets to do `executeFile` (which
wipes away both existing threads).

This example raises a general problem (which, as it turns out, is relevant
to my current work).  How can one mix multithreading with
multiprocessing?  In particular, how can a threaded process safely create
another process to run a program?  Put another way, how can the
combination of `forkProcess` and `executeFile` be done "atomically enough"
so that existing threads in the forking process don't "get in the way".

I read something on this topic (involving some sort of pervasive locking
strategy) recently, but can't recall where.  Anybody remember?

Dean Herington


Marcus Shawcroft wrote:

> Hi,
>
> I want to use a thread in concurrent haskell to manage a posix
> fork/exec/wait. I expected the test code attached below to output
> "recovering result" once, instead I get "recovering result" twice. Can
> anyone shed some light on whats going wrong?
>
> (ghci 5.02.1 x86 linux)
>
> Thanks
> /Marcus
>
> > module Test where
>
> > import Concurrent
> > import Posix
>
> > main = do
> >   mv <- newEmptyMVar
> >   forkIO $ do x <- forkProcess
> >     case x of
> >       Nothing -> do
> >         executeFile "sleep" True ["2"] Nothing
> >         error "oops"
> >       Just pid ->
> >         getProcessStatus True False pid
> >         putMVar mv ()
> >   print "recovering result"
> >   takeMVar mv