[Haskell-cafe] runInteractiveProcess leaks memory,
runInteractiveCommand does not
Andrea Rossato
mailing_list at istitutocolli.org
Mon Jun 25 15:20:44 EDT 2007
Hi,
after many test I found out that System.Process.runInteractiveProcess
leaks memory while runInteractiveCommand does.
The issue of memory leaks related to running external program was
raised here:
http://www.haskell.org/pipermail/haskell-cafe/2007-June/027234.html
and Bryan noted that after a while the process hits a steady state:
http://www.haskell.org/pipermail/haskell-cafe/2007-June/027278.html
This is true for runInteractiveCommand, but not for
runInceractiveProcess, even though, both relay on the same foreign C
imported function.
I think this is a ghc bug, but before reporting it I'd like to have
someone to confirm it.
I wrote this code that demonstrate my point. Could you please have a
look?
Thanks for you kind attention.
Andrea
here's the code.:
module Main where
import System.Process
import System.Posix.IO
import System.IO
import Control.Concurrent
readOutput rh =
do str <- hGetLine rh
return str
runWith c f =
do (i,o,e,p) <- f c
exit <- waitForProcess p
str <- readOutput o
putStrLn str
cHandles i o e
threadDelay $ 100000 * 1
runWith c f
runRunIntProcess c =
do (inp,out,err,p) <- runInteractiveProcess c [] Nothing Nothing
return (inp,out,err,p)
runRunIntCommand c =
do (inp,out,err,p) <- runInteractiveCommand c
return (inp,out,err,p)
cHandles i o e =
do hClose i
hClose o
hClose e
-- this does not leaks
-- this reaches a steady state after a while:
--virt
--5528 3404 668 S 6.6 0.7 13:07.48 procRunInComm
main = runWith "date" runRunIntProcess
-- this keep on growing
--10548 8436 676 S 8.6 1.6 13:15.24 procRunInProc
main' = runWith "date" runRunIntCommand
More information about the Haskell-Cafe
mailing list