[Haskell-cafe] Re: How to automatically free memory allocated by
malloc? and how to reliably realloc such buffer?
Simon Marlow
simonmarhaskell at gmail.com
Wed May 24 06:08:10 EDT 2006
Bulat Ziganshin wrote:
> 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)
I hope you surround each use of the actual Ptr with 'withForeignPtr'?
If so, I imagine this is safe.
I would rather package this up as a library, maybe MutForeignPtr, with
the same operations as ForeignPtr.
> 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
You can call this from inside the finalizer. There was a discussion
about this recently on one of the GHC lists, IIRC. I don't think the
FFI spec explicitly allows it.
> 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
You're missing a 'withForeignPtr'. Something like this, I think:
reallocBuffer (Mem bufRef ... fp) newsize =
withForeignPtr fp $ do
buf <- readURef bufRef
newbuf <- reallocBytes buf newsize
writeURef bufRef newbuf
Cheers,
Simon
More information about the Haskell-Cafe
mailing list