[Haskell-cafe] Re: Running a "sub-process" which dies with the main program

Aycan iRiCAN aycan.irican at core.gen.tr
Fri Jun 19 07:49:58 EDT 2009


Cum, 2009-06-19 tarihinde 13:09 +0200 saatinde, Deniz Dogan yazdı:
> 2009/6/19 Aycan iRiCAN <aycan.irican at core.gen.tr>:
> >
> > Cum, 2009-06-19 tarihinde 12:42 +0200 saatinde, Deniz Dogan yazdı:
> >> 2009/6/19 Aycan iRiCAN <aycan.irican at core.gen.tr>:
> >> >
> >> > Cum, 2009-06-19 tarihinde 11:58 +0200 saatinde, Deniz Dogan yazdı:
> >> >> 2009/6/18 Deniz Dogan <deniz.a.m.dogan at gmail.com>:
> >> >> > Hi
> >> >> >
> >> >> > I couldn't come up with a better subject than this one, so anyways...
> >> >> >
> >> >> > I have a small program which spawns a subprocess. However, when I hit
> >> >> > C-c, the subprocess won't die, instead it will just keep running until
> >> >> > it's done or until I kill it. I've looked around in System.Process for
> >> >> > something suitable for my needs, but I can't seem to find it. Any
> >> >> > ideas?
> >> >>
> >> >> With a tip from a person outside of the mailing list I found
> >> >> System.Process.system, which essentially does exactly what I was
> >> >> asking for.
> >> >
> >> > Hey I'm already subscribed :) You can read from "sout" and "serr" with
> >> > below example. Hope that it helps.
> >> >
> >> >
> >> > module Main where
> >> >
> >> > import System.Process  -- using process-1.0.1.1
> >> >
> >> > main = do
> >> >  (_, sout, serr, p) <- createProcess (proc "sleep" ["10"])
> >> >                        { std_out = CreatePipe
> >> >                        , std_err = CreatePipe }
> >> >  r <- waitForProcess p
> >> >  return ()
> >> >
> >>
> >> Thanks!
> >>
> >> But this was the approach I used before I went to
> >> System.Process.system and it did not work on my Linux machine.
> >
> > Give it a try. Try to send CTRL-C and look if "sleep 10" (which is a
> > subprocess) process terminates.
> >
> > aycan at aycan:~/haskell$ time ./deniz2 && ps -ef | grep sleep
> > ^C
> > real    0m0.707s
> > user    0m0.001s
> > sys     0m0.004s
> >   aycan 13098  4430   0 13:50:23 pts/7       0:00 grep sleep
> >
> > It terminates with ghc 6.10.3 on OpenSolaris.
> 
> This is copied verbatim from my terminal. I used the exact some code
> that you gave me.
> 
> % time ./test && ps -ef | grep sleep
> ^C
> real	0m10.005s
> user	0m0.003s
> sys	0m0.003s
> deniz    14095 14047  0 13:05 pts/1    00:00:00 grep sleep
> 
> What's strange though is that when I hit C-c *twice*, I get this behavior:

Hmm, I think GHC RTS handles SIGINT. I recompiled with thread support and got the same behavour. 

See: http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Signals

        When the interrupt signal is received, the default behaviour of
        the runtime is to attempt to shut down the Haskell program
        gracefully. It does this by calling interruptStgRts() in
        rts/Schedule.c (see Commentary/Rts/Scheduler#ShuttingDown). If a
        second interrupt signal is received, then we terminate the
        process immediately; this is just in case the normal shutdown
        procedure failed or hung for some reason, the user is always
        able to stop the process with two control-C keystrokes.

You better install signal handlers using installHandler.

Best Regards,
--
aycan



More information about the Haskell-Cafe mailing list