[Haskell-cafe] How to terminate the process group of a process created with createProcess?

André Scholz andre.scholz at uni-bremen.de
Wed Jan 11 22:26:47 CET 2012


Hello,

(on unix) creating a process A which spawns itself a subprocess B and 
terminating process A before it finishes leaves process B as a process on its 
own. This is because "terminateProcess" sends the sigterm signal to the 
process only and not to its process group.

Is there a way to terminate the process group of process A? Or alternatively 
is there a way to get he Posix ProcessId of process A?

The following is a minimal example. The process "sleep 60" survives the 
termination of both "sleep" and of the main program.

<code>

module Main where

import Control.Concurrent
import System.Process

main = do
    h@(_, _, _, hProc) <- createProcess (proc "time" ["sleep", "60"])
    threadDelay $ 5 * 1000000
    terminateProcess hProc
    waitForProcess hProc

</code>

Kind regards,
  André




More information about the Haskell-Cafe mailing list