[Haskell-cafe] memory usage in repeated reading of an external
program's output
Andrea Rossato
mailing_list at istitutocolli.org
Thu Jun 21 09:05:31 EDT 2007
On Thu, Jun 21, 2007 at 08:18:23AM -0400, Brandon S. Allbery KF8NH wrote:
>
> On Jun 21, 2007, at 6:40 , Andrea Rossato wrote:
>
> > 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.
>
> Huh. Thank you; I'd observed that behavior in one of my programs but hadn't
> sat down to figure out why yet, mostly because I have a workaround: if you
> cap the heap (+RTS -M...) it *does* do GC.
>
> Which makes it sound like something I don't know how to debug. :/
well, I followed Dougal's suggestion and riduced the program into
pieces. I'm also testing the difference of runProcess and
runInteractiveProcess. The first seems better but I need some more
test.
In the first case pipes2Handles gets 80.4% alloc.
In the second is runRunIntProcess to get 88%.
Results are pretty much the same after all.
Now I'm going to profile for memory usage: I've seen that some GC
happens if you are patient enough.
Thanks for your kind attention.
Andrea
This is the code broken up:
module Main where
import System.Process
import System.Posix.IO
import System.IO
import Control.Concurrent
readOutput rh =
do str <- hGetLine rh
return str
mkPipe =
do (r,w) <- createPipe
return (r,w)
pipes2Handles r w =
do wh <- fdToHandle w
rh <- fdToHandle r
return (rh,wh)
runRunProcess wh c =
do p <- runProcess c [] Nothing Nothing Nothing (Just wh) (Just wh)
return p
closeHandle rh wh =
do hClose wh
hClose rh
runWithRunProcess c =
do (r,w) <- mkPipe
(rh,wh) <- pipes2Handles r w
p <- runRunProcess wh c
exit <- waitForProcess p
str <- readOutput rh
closeHandle wh rh
putStrLn str
threadDelay $ 100000 * 1
runWithRunProcess c
runRunIntProcess c =
do (sin,sout,serr,p) <- runInteractiveProcess c [] Nothing Nothing
return $! (sin,sout,serr,p)
cHandles i o e =
do hClose i
hClose o
hClose e
runWithRunIntProcess c =
do (i,o,e,p) <- runRunIntProcess c
exit <- waitForProcess p
str <- readOutput o
cHandles i o e
putStrLn str
threadDelay $ 100000 * 1
runWithRunIntProcess c
main' = runWithRunProcess "date"
main = runWithRunIntProcess "date"
More information about the Haskell-Cafe
mailing list