
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

HI Gracjan,
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:
import Foreign.ForeignPtr
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: newForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a) This one worked beautifully for me. In your code something like: import Foreign.ForeignPtr hiding (newForeignPtr) import Foreign.Concurrent ... fptr <- newForeignPtr ptr (finDoIt ptr) Hope this helps, Arjan

import Foreign.ForeignPtr
I couldn't get finalisers to work either with the newForeignPtr from this module. I didn't know how to create a proper FunPtr.
You create a FunPtr using foreign import: foreign import ccall "malloc.h &free" free_ptr :: FunPtr (Ptr a -> IO ())
In Foreign.Concurrent there is a newForeignPtr that is easier to use:
But, sadly, not portable. -- Alastair Reid

Alastair Reid wrote:
import Foreign.ForeignPtr
I couldn't get finalisers to work either with the newForeignPtr from this module. I didn't know how to create a proper FunPtr.
You create a FunPtr using foreign import:
foreign import ccall "malloc.h &free" free_ptr :: FunPtr (Ptr a -> IO ())
foreign import stdcall "windows.h &UnmapViewOfFile" funptrUnmapViewOfFile :: FunPtr (Ptr a -> IO ()) Basically I'd love to do (in Windows world): mapTheFileToMemory = do handle <- winOpenFile(...) mapping <- winCreateFileMapping(...) view <- winMapViewOfFile(...) finview <- newForeignPtr funptrUnmapViewOfFile view return finview Strangely enough my finalizer run always this time, no need to say performGC or yield'ing at the end of main. But it crashes my program :( Warnings in compilation are also strange: $ ghc -package win32 --make interlvIO.hs -o interlvIO.exe Chasing modules from: interlvIO.hs Compiling Main ( interlvIO.hs, interlvIO.o ) Linking ... Warning: resolving _UnmapViewOfFile by linking to _UnmapViewOfFile@4 Use --enable-stdcall-fixup to disable these warnings Use --disable-stdcall-fixup to disable these fixups I did not find any of those flags. Searching sources downloaded from website today also does not say anything about stdcall fixups. Changing calling convention from stdcall to ccall in import clause did not help either. At the end of (correct) run my program dies with: interlvIO.exe: internal error: resumeThread: thread not found Please report this as a bug to glasgow-haskell-bugs@haskell.org, or http://www.sourceforge.net/projects/ghc/ So basically I have no idea how to make finalizer out of UnmapViewOfFile :( Any ideas where to go now? -- Gracjan

On 10-jun-04, at 17:33, Gracjan Polak wrote:
foreign import stdcall "windows.h &UnmapViewOfFile" funptrUnmapViewOfFile :: FunPtr (Ptr a -> IO ())
[...]
finview <- newForeignPtr funptrUnmapViewOfFile view return finview
Strangely enough my finalizer run always this time, no need to say performGC or yield'ing at the end of main. But it crashes my program :(
That's why I stopped using the newForeignPtr from Foreign.ForeignPtr. It also crashed. I wrote: foreign import ccall "..." finaliserCreator :: IO (FunPtr (Ptr a -> IO ())) and then finaliser <- finaliserCreator That's why I wrote: "I don't know how to make a FunPtr". I thought I knew, but then it crashed.
Any ideas where to go now?
Sorry. As I said before, the Concurrent ForeignPtr works for me. On Windows. But it may be so that the finalisers are not called at the end of the program but only at GC time. For my application this is no problem. Arjan

Arjan van IJzendoorn wrote:
foreign import ccall "..." finaliserCreator :: IO (FunPtr (Ptr a ->
IO ()))
and then
finaliser <- finaliserCreator
AFAIK this creates some dynamic machine code in malloce'd area, so there is need to free it afterward with freeHaskellFunPtr. Are you doing that? How? And when? I did not find any suitable place in my code to call freeHaskellFunPtr. -- Pozdrawiam, Regards, Gracjan

AFAIK this creates some dynamic machine code in malloce'd area, so there is need to free it afterward with freeHaskellFunPtr. Are you doing that? How? And when? I did not find any suitable place in my code to call freeHaskellFunPtr.
Machine code is dynamically created when you turn a Haskell function into a C function using Dynamic wrapper (i.e., using the "wrapper" specifier). (It might also be used for foreign exports as well since the easiest implementation is to generate a wrapper and call that as the runtime is initialized.) Dedicated users of valgrind would take care to free up all the HaskellFunPtr's generated this way but, apart from that, I'd only worry about it if: 1) There are lots of them. The dynamic machine code is quite small (probably 10-20 bytes plus another 8 bytes for malloc admin purposes). The Haskell function you're exporting will use a StablePtr which takes another 8-16 bytes. The Haskell function itself will probably be another 16 bytes or so for the closure. Overall, you're looking at less than 100 bytes per object unless... 2) The Haskell functions you are wrapping are large. For example, if you wrap: foo :: Int -> Int foo = let primes = ... in \ n -> primes !! n then the 'primes' object could get quite big and you'd worry about a space leak. As for how you keep track of them and free them. It's probably easiest to do it on the C side of things using conventional C memory management techniques (reference counting, etc.) Of course, there's a problem if you have C function pointers generated using '&' in C and function pointers generated using dynamic wrappers in Haskell. There's no reliable way to tell them apart. -- Alastair Reid

--- Gracjan Polak
foreign import stdcall "windows.h &UnmapViewOfFile" funptrUnmapViewOfFile :: FunPtr (Ptr a -> IO ())
Basically I'd love to do (in Windows world):
mapTheFileToMemory = do handle <- winOpenFile(...) mapping <- winCreateFileMapping(...) view <- winMapViewOfFile(...) finview <- newForeignPtr funptrUnmapViewOfFile view return finview
Strangely enough my finalizer run always this time, no need to say performGC or yield'ing at the end of main. But it crashes my program :(
The problem here is that the external functions (instances of type FunPtr) are always executed with ccall convention regardless of stdcall declaration in the foreign import. The workaround is to write simple stub function in C with ccall convention.
Warnings in compilation are also strange:
$ ghc -package win32 --make interlvIO.hs -o interlvIO.exe Chasing modules from: interlvIO.hs Compiling Main ( interlvIO.hs, interlvIO.o ) Linking ... Warning: resolving _UnmapViewOfFile by linking to _UnmapViewOfFile@4 Use --enable-stdcall-fixup to disable these warnings Use --disable-stdcall-fixup to disable these fixups
Try to use -fvia-C to avoid the warnings. When the program is compiled via the native code generator then windows.h isn't included and this causes the problem. __________________________________ Do you Yahoo!? Friends. Fun. Try the all-new Yahoo! Messenger. http://messenger.yahoo.com/

Krasimir Angelov wrote:
The problem here is that the external functions (instances of type FunPtr) are always executed with ccall convention regardless of stdcall declaration in the foreign import. The workaround is to write simple stub function in C with ccall convention.
You are right, I did not think about that. I would expect at least a
warning from compiler in this case.
Compilation with stub function produced perfect result. It worked.
As far as I know ia32 assembly the only thing that the stub does is
something like:
subl
Warnings in compilation are also strange:
$ ghc -package win32 --make interlvIO.hs -o interlvIO.exe Chasing modules from: interlvIO.hs Compiling Main ( interlvIO.hs, interlvIO.o ) Linking ... Warning: resolving _UnmapViewOfFile by linking to _UnmapViewOfFile@4 Use --enable-stdcall-fixup to disable these warnings Use --disable-stdcall-fixup to disable these fixups
Try to use -fvia-C to avoid the warnings. When the program is compiled via the native code generator then windows.h isn't included and this causes the problem.
-fvia-C removed warnings but the program crashes anyway without hand written stubs. At first I thought that those "stdcall-fixups" were in fact "stdcall to ccall" wrappers. OK, nevermind. -- Pozdrawiam, Regards, Gracjan

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.Concurren...): "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

[program deleted]
So, this basically means that my finalizer did not get run :( [...] It should run, in separate thread or not, it doesn't matter here.
Any ideas why doesn't it work?
Hopefully the GHC folk will correct me if I'm wrong but I think what happens is: - you allocate object with finalizer - the object becomes inaccessible - performGC causes the object to be freed by the garbage collector - the garbage collector schedules a thread to run your finalizer BUT - before the finalizer thread has a chance to be scheduled, your program exits. You could give the finalizer thread a chance to run by calling Control.Concurrent.yield before exiting: http://etudiants.insia.org/~jbobbio/pafp/docs/base/Control.Concurrent.html#v... 3Ayield That is, call yield just after calling performGC. -- Alastair Reid

Alastair Reid wrote:
You could give the finalizer thread a chance to run by calling Control.Concurrent.yield before exiting:
Thanks, it worked. This is ok for me, because my finalizer only closes some handles. Those are closed at program end anyway, so in this case I can live with it. BUT: This can make some people unhappy. Isn't there a more deterministic way to schedule finalizers? I've read about MVars etc, but this seems like an ugly hack around GC deficiency. Do weak references have same problem? Also documentation about newForeignPtr (in Control.Concurrent and in Foreign.ForeignPtr) is lying: "The only guarantee is that the finaliser runs before the program terminates." Currently there is no guarantee :) -- Gracjan

BUT: This can make some people unhappy. Isn't there a more deterministic way to schedule finalizers?
I wrote the Hugs version which does try to be more deterministic so I'm probably not the best qualified to write about what's wrong with GHC :-) But, I think part of the problem is that GHC gives the 'main' thread special status: the whole program quits when the main thread quits even if there are other threads that are runnable. There'd be less of a problem if the whole program quit only when there were no runnable threads _and_ garbage collection did not create any runnable threads. I think there's a reason why GHC gives the main thread special status though. They certainly went to some effort to give it special status so I guess there must be a good reason that they did so? -- Alastair Reid

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@csmisc79:~/tmp> ghc --make final.hs -o final Chasing modules from: final.hs Compiling Main ( final.hs, ./final.o ) Linking ... nik@csmisc79:~/tmp> ls final final.hs final.o Main.hi nik@csmisc79:~/tmp> ./final End of subproc End of program nik@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

Niklas Sorensson wrote:
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.
Yes, you are right. Thanks for the idea. Checked under GHC 6.2. -- Gracjan
participants (6)
-
Alastair Reid
-
Arjan van IJzendoorn
-
Gracjan Polak
-
Gracjan Polak
-
Krasimir Angelov
-
Niklas Sorensson