[Haskell-cafe] Handle close on GC leading to wrong reported exit codes?
Niklas Hambüchen
mail at nh2.me
Fri Aug 24 16:10:00 CEST 2012
According to System.IO, handles are automatically closed once they are
garbage-collected.
This served me well for files so far, but for processes, it gives me a
weird problem: If I don't prevent my stdErr handle from being
garbage-collected, the exit code reported by getProcessExitCode is just
wrong (for me, it's always ExitSuccess, no matter what the program does).
I posted this into #haskell and some poeple could not reproduce it, so I
wanted to ask the Cafe what happens if you run this and if you have an
idea why it happens to me.
Thank you
Niklas
The following code gives an example.
(http://hpaste.org/73593)
You can see the real exit code with "./test; echo $?".
module Main where
import Control.Concurrent (threadDelay)
import System.Process
import System.IO
import System.Exit
run :: FilePath -> [String] -> IO (Handle, Handle, Handle, ProcessHandle)
run cmd args = do
r@(i, o, e, p) <- runInteractiveProcess cmd args Nothing Nothing
getProcessExitCode p >>= \me -> case me of
Just (ExitFailure 127) -> error $ "command not found: " ++ show cmd
_ -> do
mapM_ (flip hSetBuffering LineBuffering) [i, o, e]
return r
main = do
(i, o, e, p) <- run "./test" []
putStrLn "spawned"
threadDelay 1100000
putStrLn "waited"
print =<< getProcessExitCode p
-- If you comment these away, the above always returns Just ExitSuccess
-- print =<< hGetContents o
-- print =<< hGetContents e
{- test.c:
#include <stdio.h>
#include <unistd.h>
int main(int argc, char const *argv[])
{
sleep (1);
printf ("some stdout\n");
fprintf (stderr, "some stderr\n");
fflush (stdout);
fflush (stderr);
return 2;
}
-}
More information about the Haskell-Cafe
mailing list