[Haskell-cafe] memory usage in repeated reading of an external program's output

Andrea Rossato mailing_list at istitutocolli.org
Thu Jun 21 06:40:43 EDT 2007


Hello,

I have this very simple program that executes an external program,
reads its output and prints it (the program is "date").
The readings is done with pipes.

The problem is that memory usage constantly increases over time.
Profiling does not show garbage collection of any sort.

File descriptors and handles seem to be properly closed. Still I
cannot find out where the problem lays.

Can it be related to the fact that runProcess closes the handles so
that the write file descriptor of the pipe is left open? using a
"closeFd w" after runProcess gives a Bad fd error. Moreover,
fdToHandle "converts" the fd into a handle, so I presume that closing
the second should be enough. 

And indeed  removing or inserting 
rc <- handleToFd rh
and
closeFd rc
doesn't change anything.

Thanks for your help.

Andrea

The code:

----------------
module Main where

import System.Process
import System.Posix.IO
import System.IO
import Control.Concurrent

runComLoop :: String -> IO ()
runComLoop command =
    do (r,w) <- createPipe
       wh <- fdToHandle w
       hSetBuffering wh LineBuffering
       p <- runProcess command [] Nothing Nothing Nothing (Just wh) (Just wh)
       rh <- fdToHandle r
       str <- hGetLine rh
       rc <- handleToFd rh
       hClose rh
       closeFd rc
       -- get and print the status of handles
       swh <- hShow wh
       srh <- hShow rh
       putStrLn $ show swh
       putStrLn $ show srh

       putStrLn str
       threadDelay $ 100000 * 1
       runComLoop command

main = runComLoop "date"


More information about the Haskell-Cafe mailing list