Problem with finalizers

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

Ivan
If I remember correctly there is a caveat in the documentation that
stdin/stdout could be closed when the finalizer is called. So It may
be being called - you just can see it!
Neil
On 11/05/07, Ivan Tomac
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
static inline void ctest( int *i ) { printf( "finalizer called with: %d\n", *i ); } _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Neil, I've read about that but I thought that was only the case when using finalizers written in Haskell, not in C. Also, even when I remove the call to printf and replace it with an infinite loop or a piece of code that creates a file it doesn't seem to make any difference, the finalizer never gets called. Ivan On 11/05/2007, at 9:37 PM, Neil Davies wrote:
Ivan
If I remember correctly there is a caveat in the documentation that stdin/stdout could be closed when the finalizer is called. So It may be being called - you just can see it!
Neil

It appears that if I add import Control.Concurrent and call yield just after performGC then the finalizer does get called. But it only seems to work if I call both performGC and yield and in that order. Is this normal and if so is it documented anywhere? Can this behavior be relied upon in future versions of GHC? How portable is this - I'm guessing performGC is not portable? Ivan

Ivan Tomac wrote:
It appears that if I add
import Control.Concurrent
and call yield just after performGC then the finalizer does get called. But it only seems to work if I call both performGC and yield and in that order.
There is no guarantee that a finalizer will be run before your program exits. The only thing you can be sure of is that it will *not* run while the ForeignPtr is still reachable by the garbage collector. In practice GHC will schedule the finalizer to run as soon as the GC detects that the ForeignPtr is unreachable. There will be a lag (possibly a very long lag) between the time at which the ForeignPtr becomes unreachable and the time at which a major GC is performed, and a further lag between the GC scheduling the finalizer and the finalizer actually being run. Furthermore, GHC will allow the program to exit without running all the outstanding finalizers, which is why your finalizer might not necessarily run.
Is this normal and if so is it documented anywhere?
It's documented in GHC's System.Mem.Weak module, which is used to implement ForeignPtrs in GHC. I'll add some documentation to ForeignPtr too.
Can this behavior be relied upon in future versions of GHC?
You can rely on the lack of guarantees for as long as you like :-) Cheers, Simon

Hi Simon, On 15/05/2007, at 8:31 PM, Simon Marlow wrote:
There is no guarantee that a finalizer will be run before your program exits. The only thing you can be sure of is that it will *not* run while the ForeignPtr is still reachable by the garbage collector. In practice GHC will schedule the finalizer to run as soon as the GC detects that the ForeignPtr is unreachable. There will be a lag (possibly a very long lag) between the time at which the ForeignPtr becomes unreachable and the time at which a major GC is performed, and a further lag between the GC scheduling the finalizer and the finalizer actually being run. Furthermore, GHC will allow the program to exit without running all the outstanding finalizers, which is why your finalizer might not necessarily run.
What threw me off was the part in the GHC documentation for newForeignPtr that states: "The finaliser will be executed after the last reference to the foreign object is dropped. Note that there is no guarantee on how soon the finaliser is executed after the last reference was dropped; this depends on the details of the Haskell storage manager. The only guarantee is that the finaliser runs before the program terminates." Section 5.5 of the FFI addendum has the same statement: "There is no guarantee on how soon the finalizer is executed after the last reference to the associated foreign pointer was dropped; this depends on the details of the Haskell storage manager. The only guarantee is that the finalizer runs before the program terminates." I've tried running the test code under Hugs to see how a different implementation of Haskell handles it but there were some environmental problems when running ffihugs so I gave up on that for now.
Is this normal and if so is it documented anywhere?
It's documented in GHC's System.Mem.Weak module, which is used to implement ForeignPtrs in GHC. I'll add some documentation to ForeignPtr too.
Interesting. Thanks for the info.
Can this behavior be relied upon in future versions of GHC?
You can rely on the lack of guarantees for as long as you like :-)
Heh, considering the question was a bit vague that's as good an answer as any :) What I meant was to ask for advice on whether it's better to just manually clean up instead of relying on finalizers (and performGC/ yield). Manually cleaning up handles feels a bit out of place in a language like Haskell but I suppose it's better than having prettier code that may or may not leak handles.
Cheers, Simon
Ivan
participants (3)
-
Ivan Tomac
-
Neil Davies
-
Simon Marlow