
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