Finalizers and FFI

Niklas Sorensson nik at cs.chalmers.se
Fri Jun 11 09:13:34 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]

I seem to remeber running in to this problem a couple of years ago,
and if I remember correctly, I came to the conclusion that finalizers do
run at the end of the program, but *after* standard input is closed.

However, I don't remember anymore how I came to this conclusion :) I did
manage to find some evidence in favour of this though. The following is
your program with a finalizer that is observable in other means than printing
to standard output. It simply prints somethig to a file.

{-# 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 = do
  writeFile "apa" "fisk"
  putStrLn "My finalizer"

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

main = do
     subproc
     putStrLn "End of program"


This is what happens:

nik at csmisc79:~/tmp> ghc --make final.hs -o final
Chasing modules from: final.hs
Compiling Main             ( final.hs, ./final.o )
Linking ...
nik at csmisc79:~/tmp> ls
final  final.hs  final.o  Main.hi
nik at csmisc79:~/tmp> ./final
End of subproc
End of program
nik at csmisc79:~/tmp> ls
apa  final  final.hs  final.o  Main.hi

We can see that the finalizer was run because the file was created,
but nothing was printed to the screen.

BTW, I'm using ghc 6.0.1

/Niklas



More information about the Glasgow-haskell-users mailing list