Finalizers and FFI
Gracjan Polak
gracjan at acchsh.com
Tue Jun 8 15:19:46 EDT 2004
Hi all,
I would like to attach finalizer (written in Haskell) to some pointer.
When the pointer won't be needed any more, finalizer should run. So here
is the code:
module Main where
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
foreign import stdcall "wrapper" mkFin :: (Ptr a -> IO ()) -> IO (FunPtr
(Ptr a -> IO ()))
finDoIt ptr = putStrLn "My finalizer"
mkFinalizer = mkFin finDoIt
main = do
(ptr :: Ptr Int) <- malloc
myFin <- mkFinalizer
finptr <- newForeignPtr myFin ptr
putStrLn "End of script"
This script ends with following output:
$ ./finalizers
End of script
Fail: <<loop>>
Also it seems to me that I'm not freeing finalizer stub. Is this code
leaking memory?
How do I attach finalizer to object in the heap?
--
Pozdrawiam, Regards,
Gracjan
More information about the Glasgow-haskell-users
mailing list