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

Aycan iRiCAN aycan.irican at core.gen.tr
Fri Jun 19 06:31:40 EDT 2009


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 ()


Regards,
--
aycan



More information about the Haskell-Cafe mailing list