Getting stdout and stderr as a single handle from createProcess does not work on Windows
The following test case works on Linux (an as far as I know on Mac OS X too), but not on Windows.
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Spec (main) where
import Test.HUnit
import System.Process
import System.IO
subprocess = concat $
[ "module Main where\n"
, "import System.IO\n"
, "main = do\n"
, " hPutStr stderr \"foo\"\n"
, " hFlush stderr\n"
, " hPutStrLn stdout \"bar\"\n"
, " hFlush stdout\n"
]
main = runTestTT $ TestCase $ do
(Just hin, Just hout, Nothing, _) <-
createProcess $ (proc "runhaskell" []) {
std_in = CreatePipe
, std_out = CreatePipe
, std_err = UseHandle stdout
}
hPutStrLn hin subprocess
hClose hin
line <- hGetLine hout
line @?= "foobar"
Do we consider this a bug? If not, what would be the suggested way to do that?
Trac metadata
Trac field | Value |
---|---|
Version | 7.2.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | libraries/process |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |