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

2001-12-20 Thread Dean Herington

`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


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



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

2001-12-21 Thread Simon Marlow

> 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?

I can't think of a good way to do this at the Haskell level, because
you'd need to halt all the running threads except for the one doing the
fork.  But one hack which will work is to call out to a C function which
does the fork/exec, since foreign calls will be atomic from the point of
view of the Haskell RTS.

However, one caveat which might be relevant in the future is that if the
Haskell program is running in a multi-threaded environment (i.e. OS
threads, not Haskell threads), then the C function must be marked
'unsafe' for it to be treated as atomic by the Haskell RTS.  The OS
thread support in the RTS isn't fully implemented yet, though.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



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

2002-01-14 Thread Dean Herington

It turns out that, besides having a multithreaded process do
`forkProcess` and `executeFile` "atomically", I also want to have a
multithreaded process do `forkProcess` (without `executeFile`) and
execute without any of the preexisting threads.  This can be done by
having a lock that all threads acquire before doing anything externally
visible (roughly, any `IO` action), including, of course, the
`forkProcess` itself.  This solution, however, is cumbersome and
probably inefficient.

If a foreign function invocation designated "unsafe" is atomic with
respect to the Haskell RTS, even when OS threads are used, there must be
an internal mechanism in the Haskell RTS for temporarily running
single-threaded.  Why couldn't (and shouldn't) this mechanism be
available to user programs?  It would seem to be much cleaner and more
efficient than the locking approach described above.

Dean


Simon Marlow wrote:

  > 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?

  I can't think of a good way to do this at the Haskell level, because
  you'd need to halt all the running threads except for the one doing
the
  fork.  But one hack which will work is to call out to a C function
which
  does the fork/exec, since foreign calls will be atomic from the point
of
  view of the Haskell RTS.

  However, one caveat which might be relevant in the future is that if
the
  Haskell program is running in a multi-threaded environment (i.e. OS
  threads, not Haskell threads), then the C function must be marked
  'unsafe' for it to be treated as atomic by the Haskell RTS.  The OS
  thread support in the RTS isn't fully implemented yet, though.

  Cheers,
  Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users