[Haskell-cafe] Problem with finalizers
Neil Davies
semanticphilosopher at googlemail.com
Fri May 11 07:37:57 EDT 2007
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 <tomac at pacific.net.au> wrote:
> 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 <stdio.h>
>
> static inline void ctest( int *i )
> {
> printf( "finalizer called with: %d\n", *i );
> }
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list