[Haskell-cafe] Haskell FFI and finalizers

Ryan Ingram ryani.spam at gmail.com
Wed Oct 3 13:12:57 EDT 2007


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 <mux at freebsd.org> wrote:
>        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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list