Hi, I found a workaround for this problem.
https://github.com/sol/doctest-haskell/issues/57 --Kazu > Hi, > > While I support GHC head for "doctest", I encountered the following > bug. > > "doctest" uses a GHCi subprocess to evaluate an expression represented > in String. Stderr from GHCi is merged into stdout by hDuplicateTo in > the GHCi side. Even evaluating an error expression, for instance "1 > `div` 0", the line buffering does not work. "doctest" waits for output > from GHCi forever. This does not happen if stderr is not merged into > stdout. > > The following code demonstrates this bug. Running it with GHC head > waits forever. Running it with GHC 7.6.3 prints: > "*** Exception: divide by zero" > "3" > > If you change "1 `div` 0" into "1 `div` 0\nprint 10", this code run by > GHC head prints: > "*** Exception: divide by zero" > "10" > > This is a serious behavior change for "doctest". I hope this will be > fixed. > > --Kazu > > module Main where > > import System.Process > import System.IO > > myProc :: CreateProcess > myProc = (proc "ghc" ["-v0", "--interactive", "-ignore-dot-ghci"]) { > std_in = CreatePipe > , std_out = CreatePipe > , std_err = Inherit > } > > setMode :: Handle -> IO () > setMode hdl = do > hSetBinaryMode hdl False > hSetBuffering hdl LineBuffering > > newInterpreter :: IO (Handle, Handle) > newInterpreter = do > (Just stdin_, Just stdout_, _, _) <- createProcess myProc > setMode stdin_ > setMode stdout_ > hPutStrLn stdin_ "import System.IO" > hPutStrLn stdin_ "import GHC.IO.Handle" > hPutStrLn stdin_ "hDuplicateTo stdout stderr" > hFlush stdin_ > return (stdin_, stdout_) > > eval :: Handle -> Handle -> String -> IO String > eval hin hout expr = do > hPutStrLn hin expr > hFlush hin > hGetLine hout > > main :: IO () > main = do > (stdin_, stdout_) <- newInterpreter > eval stdin_ stdout_ "1 `div` 0" >>= print > eval stdin_ stdout_ "1 + 2" >>= print > return () > > > _______________________________________________ > ghc-devs mailing list > ghc-devs@haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs