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

Deniz Dogan deniz.a.m.dogan at gmail.com
Fri Jun 19 06:42:51 EDT 2009


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. Looking
at the source code for "system", we see that it uses "syncProcess",
which has #ifdef mingw32_HOST_OS (IIRC) in which the code you gave me
resides. If mingw32_HOST_OS is not defined, one has to go through
quite a bit more trouble to get the same effect.

This is why it bugs me a bit that syncProcess is not exported. I can't
find any reason not to export it, but what do I know?

-- 
Deniz Dogan


More information about the Haskell-Cafe mailing list