[Haskell-cafe] Problem with finalizers

Ivan Tomac tomac at pacific.net.au
Fri May 11 06:22:50 EDT 2007


Why does the finalizer in the following code never get called unless  
I explicitly call finalizeForeignPtr fptr?
Even adding System.Mem.performGC made no difference.

The code was compiled with ghc --make -fffi -fvia-c Test.hs

Ivan

-------------------- Test.hs ------------------------

module Main where

import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Marshal.Utils

import System.Mem

foreign import ccall safe "ctest.h &ctest" ctestPtr :: FunPtr (Ptr  
Int -> IO ())

test :: Int -> IO ()
test i = with i test'
     where
         test' ptr = do fptr <- newForeignPtr ctestPtr ptr
                        putStrLn "test"
--                       finalizeForeignPtr fptr

main = do putStrLn "before test..."
           test 33
           putStrLn "after test..."
           performGC

--------------------- ctest.h ----------------------

#include <stdio.h>

static inline void ctest( int *i )
{
     printf( "finalizer called with: %d\n", *i );
}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070511/120031a4/attachment-0001.htm


More information about the Haskell-Cafe mailing list