How to automatically free memory allocated by malloc? and how to reliably realloc such buffer?

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@gmail.com

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

Hello Simon, Wednesday, May 24, 2006, 2:08:10 PM, you wrote:
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.
no, i hope that fptr's finalizers will be no executed as long as perform any operations on this Mem structure. i think that there should be no problems as long as bufRef not returned from functions working with Mem, like this -- problematic code: vRequestBuf (Mem bufRef ... fptr) = do readURef bufRef makeProblems = do mem <- newMem buf <- vRequestBuf mem poke buf 0 -- at this time buffer may be already deallocated -- because 'mem' is not further referenced
I would rather package this up as a library, maybe MutForeignPtr, with the same operations as ForeignPtr.
it seems not so easy hack as i thought. first and obvious is that wrapping all buffer pointers to the ForeignPtr will be rather slow on ghc 6.4. second and not so obvious is model of buffers' usage now i've modified MemoryStream interface to the following: class (Stream IO h) => MemoryStream h where -- | Request access to memory buffer for READING or WRITING. -- Operation returns 'pos' and 'end' - pointers to the start and after-end -- part of buffer available for reading or writing. -- It returns pos==end if there is no more data to read (vIsEOF) -- or no more space to write to (for streams with limited size). -- In other cases buffer received by this call must be released by call -- to 'vReleaseBuf' vRequestBuf :: h -> ReadWrite -> IO (Ptr a, Ptr b) -- | Release buffer that was received via call to 'vRequestBuf' and -- tells new position after some number of bytes at the start of buffer was -- read or written. After this call buffer is no more available for any -- operation vReleaseBuf :: h -> ReadWrite -> Ptr a -> IO () as an example of it's usage is the following function that implements vPutChar for any MemoryStream: fastPutChar s c = do (pos,end) <- vRequestBuf s WRITING if pos==end then vThrow s fullErrorType else do writeByteAt pos $! (ord c) vReleaseBuf s WRITING $! (pos+:1) it seems that scheme with ForeignPtr will be fast and reliable if both the following conditions are met: 1. stream transformer got access to the buffer only through the 'vRequestBuf' and ALWAYS releases it after use with call to 'vReleaseBuf'. 2. base Stream use ForeignPtr to hold finalizer. this ForeignPtr is touched in the 'vReleaseBuf' and after any buffer reallocation but the problem is what i can't use vRequestBuf/vReleaseBuf in highly optimized code, it's too slow. does 'touchForeignPtr' require any time to execute or it is no-op that have meaning only for program analysis? may be it's better just to require from user to explicitly execute 'vClose' operation...
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
i agree that withForeignPtr required here to ensure that 'fp' will not run it's finalzer just at this moment. but it seems that 'block' ia ALSO required to ensure that 'bufRef' after 'realloc' will be updated with new value -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Wednesday, May 24, 2006, 2:08:10 PM, you wrote:
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.
no, i hope that fptr's finalizers will be no executed as long as perform any operations on this Mem structure. i think that there should be no problems as long as bufRef not returned from functions working with Mem, like this
-- problematic code: vRequestBuf (Mem bufRef ... fptr) = do readURef bufRef
makeProblems = do mem <- newMem buf <- vRequestBuf mem poke buf 0 -- at this time buffer may be already deallocated -- because 'mem' is not further referenced
This isn't safe, I'm afraid. Suppose GHC inlined vRequestBuf, and discovered that fptr isn't used so discarded the reference to it. Then the ForeignPtr could be finalized too early. You can either use withForeignPtr around each operation that accesses the Ptr, or you can use touchForeignPtr at the end of each operation.
it seems not so easy hack as i thought. first and obvious is that wrapping all buffer pointers to the ForeignPtr will be rather slow on ghc 6.4. second and not so obvious is model of buffers' usage
now i've modified MemoryStream interface to the following:
class (Stream IO h) => MemoryStream h where -- | Request access to memory buffer for READING or WRITING. -- Operation returns 'pos' and 'end' - pointers to the start and after-end -- part of buffer available for reading or writing. -- It returns pos==end if there is no more data to read (vIsEOF) -- or no more space to write to (for streams with limited size). -- In other cases buffer received by this call must be released by call -- to 'vReleaseBuf' vRequestBuf :: h -> ReadWrite -> IO (Ptr a, Ptr b)
-- | Release buffer that was received via call to 'vRequestBuf' and -- tells new position after some number of bytes at the start of buffer was -- read or written. After this call buffer is no more available for any -- operation vReleaseBuf :: h -> ReadWrite -> Ptr a -> IO ()
This is slightly off-topic, but the request/release design forces the upper layer to do the exception handling (eg. with Control.Exception.bracket), whereas a with-style design would include the exception handling and make the API less error-prone to use. If you're inside a block it's easier, but you still have to worry about synchronous exceptions.
as an example of it's usage is the following function that implements vPutChar for any MemoryStream:
fastPutChar s c = do (pos,end) <- vRequestBuf s WRITING if pos==end then vThrow s fullErrorType else do writeByteAt pos $! (ord c) vReleaseBuf s WRITING $! (pos+:1)
it seems that scheme with ForeignPtr will be fast and reliable if both the following conditions are met:
1. stream transformer got access to the buffer only through the 'vRequestBuf' and ALWAYS releases it after use with call to 'vReleaseBuf'.
2. base Stream use ForeignPtr to hold finalizer. this ForeignPtr is touched in the 'vReleaseBuf' and after any buffer reallocation
but the problem is what i can't use vRequestBuf/vReleaseBuf in highly optimized code, it's too slow. does 'touchForeignPtr' require any time to execute or it is no-op that have meaning only for program analysis?
Yes, it's a no-op.
may be it's better just to require from user to explicitly execute 'vClose' operation...
I don't think that would be a good design.
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
i agree that withForeignPtr required here to ensure that 'fp' will not run it's finalzer just at this moment. but it seems that 'block' ia ALSO required to ensure that 'bufRef' after 'realloc' will be updated with new value
Yes, that's true. Cheers, Simon
participants (2)
-
Bulat Ziganshin
-
Simon Marlow