[Haskell-cafe] How to automatically free memory allocated by
malloc? and how to reliably realloc such buffer?
Bulat Ziganshin
bulat.ziganshin at gmail.com
Sun May 21 04:52:19 EDT 2006
Hello Haskell-Cafe,
my program uses datastructure that contains plain Ptr, this Ptr points
to the memory area allocated by 'malloc':
createRawMemBuf size = do
buf <- mallocBytes (fromIntegral size)
bufRef <- newURef buf
...
return (Mem bufRef ...)
i need to free this memory buffer on GC if there are no more references
to Mem structure. how i can accomplish this? i can't allocate this
buffer in GHC heap because later i can use 'realloc' on it.
i think that i should use ForeignPtr what points to nothing
and performs 'readURef bufRef >>= free' in it's finalizer?
something like this:
createRawMemBuf size = do
buf <- mallocBytes (fromIntegral size)
bufRef <- newURef buf
...
fin <- mkFinalizer (\_ -> readURef bufRef >>= free)
fptr <- newForeignPtr fin nullPtr
return (Mem bufRef ... fptr)
type Finalizer a = Ptr a -> IO ()
foreign import ccall "wrapper"
mkFinalizer :: Finalizer a -> IO (FinalizerPtr a)
... well, i implemented this and it seems to work - at least memory
freed at performGC. another question is how to free 'fin' - i should
apply 'freeHaskellFunPtr' to it, but i think i can't do it in finalizer
itself
The second question is how to make buffer reallocation reliable.
Currently i use the following code:
reallocBuffer (Mem bufRef ...) newsize = do
buf <- readURef bufRef
writeURef bufRef nullPtr
newbuf <- reallocBytes buf newsize
writeURef bufRef newbuf
First 'writeURef' is used to prevent repetitive memory deallocation by
finalizer i this routine will be interrupted just after 'reallocBytes'
operation. will it be enough to use 'block' instead? i.e.:
reallocBuffer (Mem bufRef ...) newsize = do
buf <- readURef bufRef
block $ do
newbuf <- reallocBytes buf newsize
writeURef bufRef newbuf
--
Best regards,
Bulat mailto:Bulat.Ziganshin at gmail.com
More information about the Haskell-Cafe
mailing list