[Haskell-cafe] Re[2]: How to automatically free memory allocated by malloc? and how to reliably realloc such buffer?

Bulat Ziganshin bulat.ziganshin at gmail.com
Wed May 24 09:29:25 EDT 2006


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



More information about the Haskell-Cafe mailing list