
Hello all, I have recently developed a small set of bindings for a C library, and encountered a problem that I think could be interesting to others. My problem was that the C function I was writing bindings to expects to be passed a FILE *. So, I had basically two possibles routes to take: 1) Mimic the C API and have the haskell function take a Handle. Unfortunately, I can see no way to go from a Handle to a Ptr CFile, at least no portable way, so I discarded this option. 2) Deviate from the C API slightly and have the haskell function take a FilePath instead of a Handle. This is the option I chose, and this is where things get interesting. In order to pass a Ptr CFile (FILE *) to the C function, I had to call fopen() myself, using a usual FFI binding: foreign import ccall unsafe "fopen" fopen :: CString -> CString -> IO (Ptr CFile) That's the easy part. Now my problem was that I had to find a way to automatically close this FILE * when it isn't used anymore, in order not to leak FILE structures (and thus fds, etc). A finalizer is typically what I need, but unfortunately, a finalizer has a very strict shape: type FinalizerPtr a = FunPtr (Ptr a -> IO ()) That is, a finalizer can only be a pointer to a foreign function, and the foreign function itself needs a quite specific shape. And then I discovered Foreign.Concurrent, which allows one to associate a plain Haskell IO action to a pointer. The 'Foreign.Concurrent' name is a bit misleading to me; it seems this module is named so because it needs concurrency itself, rather than providing stuff for concurrency. So, in the end, I've got this code: import Foreign import Foreign.C import qualified Foreign.Concurrent as FC ... data PlayerStruct type Player = ForeignPtr PlayerStruct ... foreign import ccall unsafe "dd_newPlayer_file" dd_newPlayer_file :: Ptr CFile -> Ptr ImageStruct -> IO (Ptr PlayerStruct) foreign import ccall unsafe "&dd_destroyPlayer" destroyPlayerFinal :: FunPtr (Ptr PlayerStruct -> IO ()) foreign import ccall unsafe "fopen" fopen :: CString -> CString -> IO (Ptr CFile) foreign import ccall unsafe "fclose" fclose :: Ptr CFile -> IO CInt ... mkFinalizedPlayer :: Ptr PlayerStruct -> IO Player mkFinalizedPlayer = newForeignPtr destroyPlayerFinal newPlayerFile :: FilePath -> Image -> IO Player newPlayerFile path image = do withCString path $ \cpath -> do withCString "rb" $ \cmode -> do file <- throwErrnoIfNull "fopen: " (fopen cpath cmode) withForeignPtr image $ \ptr -> do player <- dd_newPlayer_file file ptr >>= mkFinalizedPlayer FC.addForeignPtrFinalizer player (fclose file >> return ()) return player So I'm adding the "usual" finalizer, and with the help of Foreign.Concurrent, I can add a second free-form one (fclose file >> return ()), in order to close the file I opened at an appropriate time. I'm looking forward hearing about other people's opinions, and wether this is a correct solution to the initial problem or not. I think there is another way to solve this, which is to provide the finalizer still in haskell code, but export the haskell code using FFI, so that I can use it as a plain, normal finalizer. I'm still unsure about this. Cheers, Maxime

Hello Maxime, Wednesday, October 3, 2007, 7:57:58 PM, you wrote:
And then I discovered Foreign.Concurrent, which allows one to associate a plain Haskell IO action to a pointer. The 'Foreign.Concurrent' name is a bit misleading to me; it seems this module is named so because it needs concurrency itself, rather than providing stuff for concurrency.
such finalizer cannot be run w/o concurrency support. you can find explanations in module docs. shortly speaking, finalizing occurs at time of GC and there is no way to run Haskell code at this moment except than using another Haskell thread -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

I think you want to use "wrapper" functions from the FFI:
type HsPlayerFinalizer = Ptr PlayerStruct -> IO ()
foreign import ccall "wrapper" mkPlayerFinalizer :: HsPlayerFinalizer
-> IO (FunPtr HsPlayerFinalizer)
You can then make an arbitrary Haskell function (including a partially
applied function with closure state) into a FunPtr. You call
freeHaskellFunPtr when you are done with the function pointer.
I believe it's safe to do this from the finalizer itself; you can use
something like
mkFinalizerPlayer ptr file = mdo
finalizer <- mkPlayerFinalizer (createFinalizer finalizer file)
newForeignPtr finalizer ptr
where
createFinalizer finalizer file player = do
destroyPlayer player
fclose file
freeHaskellFunPtr finalizer
-- ryan
On 10/3/07, Maxime Henrion
Hello all,
I have recently developed a small set of bindings for a C library, and encountered a problem that I think could be interesting to others.
My problem was that the C function I was writing bindings to expects to be passed a FILE *. So, I had basically two possibles routes to take:
1) Mimic the C API and have the haskell function take a Handle.
Unfortunately, I can see no way to go from a Handle to a Ptr CFile, at least no portable way, so I discarded this option.
2) Deviate from the C API slightly and have the haskell function take a FilePath instead of a Handle.
This is the option I chose, and this is where things get interesting.
In order to pass a Ptr CFile (FILE *) to the C function, I had to call fopen() myself, using a usual FFI binding:
foreign import ccall unsafe "fopen" fopen :: CString -> CString -> IO (Ptr CFile)
That's the easy part. Now my problem was that I had to find a way to automatically close this FILE * when it isn't used anymore, in order not to leak FILE structures (and thus fds, etc). A finalizer is typically what I need, but unfortunately, a finalizer has a very strict shape:
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
That is, a finalizer can only be a pointer to a foreign function, and the foreign function itself needs a quite specific shape.
And then I discovered Foreign.Concurrent, which allows one to associate a plain Haskell IO action to a pointer. The 'Foreign.Concurrent' name is a bit misleading to me; it seems this module is named so because it needs concurrency itself, rather than providing stuff for concurrency.
So, in the end, I've got this code:
import Foreign import Foreign.C import qualified Foreign.Concurrent as FC
...
data PlayerStruct type Player = ForeignPtr PlayerStruct
...
foreign import ccall unsafe "dd_newPlayer_file" dd_newPlayer_file :: Ptr CFile -> Ptr ImageStruct -> IO (Ptr PlayerStruct) foreign import ccall unsafe "&dd_destroyPlayer" destroyPlayerFinal :: FunPtr (Ptr PlayerStruct -> IO ())
foreign import ccall unsafe "fopen" fopen :: CString -> CString -> IO (Ptr CFile) foreign import ccall unsafe "fclose" fclose :: Ptr CFile -> IO CInt
...
mkFinalizedPlayer :: Ptr PlayerStruct -> IO Player mkFinalizedPlayer = newForeignPtr destroyPlayerFinal
newPlayerFile :: FilePath -> Image -> IO Player newPlayerFile path image = do withCString path $ \cpath -> do withCString "rb" $ \cmode -> do file <- throwErrnoIfNull "fopen: " (fopen cpath cmode) withForeignPtr image $ \ptr -> do player <- dd_newPlayer_file file ptr >>= mkFinalizedPlayer FC.addForeignPtrFinalizer player (fclose file >> return ()) return player
So I'm adding the "usual" finalizer, and with the help of Foreign.Concurrent, I can add a second free-form one (fclose file >> return ()), in order to close the file I opened at an appropriate time.
I'm looking forward hearing about other people's opinions, and wether this is a correct solution to the initial problem or not.
I think there is another way to solve this, which is to provide the finalizer still in haskell code, but export the haskell code using FFI, so that I can use it as a plain, normal finalizer. I'm still unsure about this.
Cheers, Maxime _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Oct 03, 2007 at 05:57:58PM +0200, Maxime Henrion wrote:
I have recently developed a small set of bindings for a C library, and encountered a problem that I think could be interesting to others.
My problem was that the C function I was writing bindings to expects to be passed a FILE *. So, I had basically two possibles routes to take:
That's the easy part. Now my problem was that I had to find a way to automatically close this FILE * when it isn't used anymore, in order not to leak FILE structures (and thus fds, etc). A finalizer is typically what I need, but unfortunately, a finalizer has a very strict shape:
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
That is, a finalizer can only be a pointer to a foreign function, and the foreign function itself needs a quite specific shape.
And then I discovered Foreign.Concurrent, which allows one to associate a plain Haskell IO action to a pointer. The 'Foreign.Concurrent' name is a bit misleading to me; it seems this module is named so because it needs concurrency itself, rather than providing stuff for concurrency.
NOOO! Foreign.Concurrent, as its name implies, works by forking threads, and it should be avoided at almost any cost. The correct solution is: void close_file_finalizer(FILE *file) { if (fclose(file) < 0) { /* do something sensible here */ } }
I think there is another way to solve this, which is to provide the finalizer still in haskell code, but export the haskell code using FFI, so that I can use it as a plain, normal finalizer. I'm still unsure about this.
Calling Haskell code from the garbage collector is essentially impossible to do efficiently and correctly. Don't even try it, your sanity is not worth saving 3 lines of C coding. Stefan

Stefan O'Rear wrote:
On Wed, Oct 03, 2007 at 05:57:58PM +0200, Maxime Henrion wrote:
I have recently developed a small set of bindings for a C library, and encountered a problem that I think could be interesting to others.
My problem was that the C function I was writing bindings to expects to be passed a FILE *. So, I had basically two possibles routes to take:
That's the easy part. Now my problem was that I had to find a way to automatically close this FILE * when it isn't used anymore, in order not to leak FILE structures (and thus fds, etc). A finalizer is typically what I need, but unfortunately, a finalizer has a very strict shape:
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
That is, a finalizer can only be a pointer to a foreign function, and the foreign function itself needs a quite specific shape.
And then I discovered Foreign.Concurrent, which allows one to associate a plain Haskell IO action to a pointer. The 'Foreign.Concurrent' name is a bit misleading to me; it seems this module is named so because it needs concurrency itself, rather than providing stuff for concurrency.
NOOO! Foreign.Concurrent, as its name implies, works by forking threads, and it should be avoided at almost any cost. The correct solution is:
void close_file_finalizer(FILE *file) { if (fclose(file) < 0) { /* do something sensible here */ } }
That wouldn't work; my problem is that this finalizer for closing the FILE * needs to be called when another pointer gets garbage collected. This is because I'm opening the file in order to pass to some function which creates an objet and returns it to me. To parody the situation: struct foo *foo_new(FILE *); void foo_destroy(struct foo *); When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo * object, I want to also close the FILE * handle. If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use. Thanks, Maxime

On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote:
When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo * object, I want to also close the FILE * handle.
If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use.
Ah, yes, this does make the situation more interesting. Looks like newForeignPtrEnv is maybe what you want? Stefan

Stefan O'Rear wrote:
On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote:
When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo * object, I want to also close the FILE * handle.
If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use.
Ah, yes, this does make the situation more interesting.
Looks like newForeignPtrEnv is maybe what you want?
Yeah, this is what I use now. I wrote a player_finalizer() function in C, that takes a FILE * and a pointer to the struct I'm handling, and which just closes the file. I then added these sources to the mix in my .cabal file (with C-Sources, Extra-Includes, etc), and registered this new finalizer using addForeignPtrFinalizerEnv. This makes me want to ask you, what is so bad about Foreign.Concurrent that it should be avoided at almost any cost? It sure is likely to be much slower than just calling a plain C finalizer, but aren't Haskell threads super-cheap anyways? I'm not doubting your advices at all, but want to make sure I understand all this fully :-). Thanks again, Maxime

Maxime Henrion wrote:
Stefan O'Rear wrote:
On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote:
When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo * object, I want to also close the FILE * handle.
If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use. Ah, yes, this does make the situation more interesting.
Looks like newForeignPtrEnv is maybe what you want?
Yeah, this is what I use now. I wrote a player_finalizer() function in C, that takes a FILE * and a pointer to the struct I'm handling, and which just closes the file. I then added these sources to the mix in my .cabal file (with C-Sources, Extra-Includes, etc), and registered this new finalizer using addForeignPtrFinalizerEnv.
This makes me want to ask you, what is so bad about Foreign.Concurrent that it should be avoided at almost any cost? It sure is likely to be much slower than just calling a plain C finalizer, but aren't Haskell threads super-cheap anyways?
In GHC ordinary ForeignPtr finalizers are implemented using Foreign.Concurrent anyway. It's not so much that Foreign.Concurrent should be avoided at all costs, but rather finalizers in general should be avoided, especially if you really care about when they run (i.e. bad things could happen if they run late or at unpredictable times). The Haskell code is not run "by the garbage collector", rather the garbage collector figures out which finalizers need running and creates a thread to run them. It's perfectly safe to have C finalizers that invoke Haskell code using GHC, although this is explicitly undefined by the FFI spec. The reason that Foreign.Concurrent is separate from Foreign.ForeignPtr is that it does essentially require concurrency to implement, whereas ordinary C finalizers can be run by the GC (although GHC doesn't do it this way). Cheers, Simon

Simon Marlow wrote:
Maxime Henrion wrote:
Stefan O'Rear wrote:
On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote:
When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo * object, I want to also close the FILE * handle.
If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use. Ah, yes, this does make the situation more interesting.
Looks like newForeignPtrEnv is maybe what you want?
Yeah, this is what I use now. I wrote a player_finalizer() function in C, that takes a FILE * and a pointer to the struct I'm handling, and which just closes the file. I then added these sources to the mix in my .cabal file (with C-Sources, Extra-Includes, etc), and registered this new finalizer using addForeignPtrFinalizerEnv.
This makes me want to ask you, what is so bad about Foreign.Concurrent that it should be avoided at almost any cost? It sure is likely to be much slower than just calling a plain C finalizer, but aren't Haskell threads super-cheap anyways?
In GHC ordinary ForeignPtr finalizers are implemented using Foreign.Concurrent anyway. It's not so much that Foreign.Concurrent should be avoided at all costs, but rather finalizers in general should be avoided, especially if you really care about when they run (i.e. bad things could happen if they run late or at unpredictable times).
The Haskell code is not run "by the garbage collector", rather the garbage collector figures out which finalizers need running and creates a thread to run them. It's perfectly safe to have C finalizers that invoke Haskell code using GHC, although this is explicitly undefined by the FFI spec.
The reason that Foreign.Concurrent is separate from Foreign.ForeignPtr is that it does essentially require concurrency to implement, whereas ordinary C finalizers can be run by the GC (although GHC doesn't do it this way).
Thank you for those precisions, Simon. It seems that even if using the Foreign.Concurrent module isn't a problem per-self, I'd be better off using a plain C finalizer that I write myself, if only for portability with other FFI implementations. Cheers, Maxime

Hello Maxime, Thursday, October 4, 2007, 2:55:41 AM, you wrote:
If I write a small C function for doing the finalizer myself, I still wouldn't get passed the FILE * to close, only the struct foo * pointer which is of no use.
you can use global assocs list -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (6)
-
Bulat Ziganshin
-
Jules Bean
-
Maxime Henrion
-
Ryan Ingram
-
Simon Marlow
-
Stefan O'Rear