Memory leak in FFI callback: GHC 6.6
SevenThunders
mattcbro at earthlink.net
Thu Nov 2 21:54:27 EST 2006
I'm not sure if this is a bug, but it sure seems that way to me. When using
the "wrapper" technique for creating a Haskell callback function it seems
that freeHaskellFunPtr is not properly freeing the resource.
Here is an example program
<leaky.hs>
module Main where
import Foreign
import Foreign.Ptr
import Foreign.Storable
-- | A convenient type synonym for storable arrays
type Darr = Ptr (Double)
-- | Function type for mapping doubles to doubles
type Dfunc = Double -> Double
-- | A convenient type synonym for monad containing storable arrays
type IODarr = IO (Darr)
foreign import ccall "wrapper" mkDfunc :: Dfunc -> IO (FunPtr Dfunc)
foreign import ccall "cleaky.h cfunc" cfunc :: (FunPtr Dfunc) -> IO ( Double
)
dadd :: Dfunc
dadd x = x + 1.0
getleaky :: Dfunc -> IO ()
getleaky cf = do
pcf <- mkDfunc cf
-- pd <- cfunc pcf
print pcf
freeHaskellFunPtr pcf
main = sequence_ [getleaky dadd | q <- [1..500000]]
It's compiled with
ghc -fglasgow-exts -fffi -prof -auto -I. --make leaky.hs cleaky.o
A possible cleaky.c and cleaky.h are
#include <math.h>
#include <stdio.h>
#include "cleaky.h"
double state = 1.0 ;
double cfunc(DFptr fptr)
{
// printf("In cfunc, fptr: %p\n", fptr) ;
state = (*fptr) (state) ;
// printf("state: %g\n", state) ;
return(state) ;
}
typedef double (*DFptr) (double) ;
double cfunc(DFptr) ;
though they are not used.
leaky.exe grows the heap linearly without bound on windows XP 64. The
profiler never reports this correctly either.
calling
leaky +RTS -hc -RTS
does not show the increase in the memory usage.
--
View this message in context: http://www.nabble.com/Memory-leak-in-FFI-callback%3A-GHC-6.6-tf2565446.html#a7150757
Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.
More information about the Glasgow-haskell-users
mailing list