[Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

Olivier Boudry olivier.boudry at gmail.com
Thu May 15 13:40:34 EDT 2008


Hi all,

It's the first time I use the runInteractiveCommand and I was probably
bitten by laziness.

When I run the following program and send its output to a file using '>'
redirection I get the full output of the called process. But if I run it in
the console I get only half of the output. As console is slower than disk I
assume the called process terminates before all data has been read from it
or the main process terminates before data has been written to stdout. I
thought using waitForProcess, closing called process output and flushing
stdout would solve the problem but it doesn't.

> -- Compile with -threaded option
> module Main where
>
> import Control.Concurrent (forkIO)
> import System.Environment (getArgs)
> import System.FilePath (dropExtension, takeFileName)
> import System.IO (Handle, hClose, hFlush, hGetContents, stdout)
> import System.Process (runInteractiveCommand, waitForProcess)
>
> main :: IO ()
> main = do
>   (file:_) <- getArgs
>   (_, out, _, pid) <- runInteractiveCommand $ "dumpbin /EXPORTS " ++ file
>   forkIO (createDefFile file out)
>   waitForProcess pid
>   hClose out
>   hFlush stdout
>
> createDefFile :: String -> Handle -> IO ()
> createDefFile file inp = do
>   putStrLn $ "LIBRARY " ++ (dropExtension . takeFileName) file ++ ".dll"
>   putStrLn "EXPORTS"
>   text <- hGetContents inp
>   mapM_ writeExport $ keepExports $ map words $ lines text
>   where
>     keepExports :: [[String]] -> [String]
>     keepExports = map head
>                   . filter (not . null)
>                   . takeWhile (["Summary"]/=)
>                   . drop 1
>                   . dropWhile (["ordinal","name"]/=)
>     writeExport ('_':xs) = putStrLn xs
>     writeExport xs = putStrLn xs

Any idea regarding the cause of this problem?

Thanks,

Olivier.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080515/f8360f17/attachment.htm


More information about the Haskell-Cafe mailing list