Finalizers and FFI

Gracjan Polak gracjan at student.uci.agh.edu.pl
Thu Jun 10 04:22:01 EDT 2004



Arjan van IJzendoorn wrote:
 > I couldn't get finalisers to work either with the newForeignPtr from
 > this module. I didn't know how to create a proper FunPtr. In
 > Foreign.Concurrent there is a newForeignPtr that is easier to use:
 > [deleted]

So here is the new code:

{-# OPTIONS -fglasgow-exts #-}
module Main where
import Foreign.Ptr
import Foreign.ForeignPtr hiding (newForeignPtr)
import Foreign.Marshal.Alloc
import Foreign.Concurrent
import System.Mem

myFinalizer = putStrLn "My finalizer"

subproc = do
     (ptr :: Ptr Int) <- malloc
     finptr <- newForeignPtr ptr myFinalizer
     putStrLn "End of subproc"

main = do
     subproc
     performGC
     putStrLn "End of program"


This program compiled under GHC 6.2 gives follwing output:

$ ./finalizers
End of subproc
End of program

So, this basically means that my finalizer did not get run :( Strange 
thing to me. Spec says 
(http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign.Concurrent.html):

"The finalizer will be executed after the last reference to the foreign 
object is dropped. Note that there is no guarantee on how soon the 
finalizer is executed after the last reference was dropped; this depends 
on the details of the Haskell storage manager. The only guarantee is 
that the finalizer runs before the program terminates."

It should run, in separate thread or not, it doesn't matter here.

Any ideas why doesn't it work?


-- 
Gracjan




More information about the Glasgow-haskell-users mailing list