Is it safe to call getProcessExitCode more than once?

Peter Simons simons at cryp.to
Sat Oct 30 08:37:19 EDT 2004


Glynn Clements writes:

 > Although, depending upon the OS, setting SIGCHLD to
 > SIG_IGN may cause processes to be reaped automatically
 > (i.e. not become zombies), so that's a possible
 > alternative.

I think I've got it under control now. I'm using this
wrapper to make sure there are no unwaited-for child
processes:

  type ExternHandle = MVar (Handle, Handle, Handle, ProcessHandle)

  -- |Run an external process and store its handle in an
  -- 'MVar' with a finalizer attached to it that will close
  -- the handles and kill the process when the MVar falls out
  -- of scope.

  extern :: FilePath -> [String] -> IO ExternHandle
  extern path args = do
    r <- runInteractiveProcess path args (Just "/") (Just [])
    mv <- newMVar r
    addMVarFinalizer mv (catch (cleanup r) (const (return ())))
    return mv
      where
      cleanup (hin, hout, herr, pid) = do
        terminateProcess pid >> safeWaitForProcess pid
        hClose hin >> hClose hout >> hClose herr
        return ()

  -- |Wait 10 seconds max. If the process hasn't terminated by
  -- then, throw an exception. If the child process has been
  -- terminated by a signal, return @ExitFailure 137 at . This is
  -- a kludge. So it will probably be in here forever.

  safeWaitForProcess :: ProcessHandle -> IO ExitCode
  safeWaitForProcess pid =
    timeout maxwait loop >>= maybe badluck return
      where
      loop    = catch loop' (\_ -> return (ExitFailure 137))
      loop'   = wait >> getProcessExitCode pid >>= maybe loop' return
      wait    = threadDelay 1000000 -- 1/10 second
      maxwait = 10000000            -- 10 seconds
      badluck = fail "timeout while waiting for external process"

It's ugly, but it seems to work.

Peter



More information about the Glasgow-haskell-users mailing list