Hello. I'm having a minor annoyance with the FFI, and was wondering if there was a better solution available.
{-# LANGUAGE ForeignFunctionInterface #-}
module FFITest where
import Foreign
Suppose we are interfacing with a foreign library that uses callbacks,for instance, suppose we have "void register_callback(void (*callback)(void));"
foreign import ccall "register_callback" registerCallback :: FunPtr (IO ()) -> IO ()
And we have a Haskell function that we want to register:
myCallback :: IO () myCallback = undefined
So how do we do this? The simplest option is to use a dynamic wrapper:
foreign import ccall "wrapper" wrapCallback :: IO () -> IO (FunPtr (IO ()))registerMy :: IO () registerMy = wrapCallback myCallback >>= registerCallback
However, this is not really ideal: * We don't have a single global FunPtr, but we have to create a new one as an IO action. If we do the registration many times, we end up creating multiple wrappers for the same Haskell function, which is a bit wasteful. * Further, since the the FunPtr has been dynamically allocated, we have to remember to ensure that freeHaskellFunPtr gets called when the callback is no longer used. * Finally, I'm rather uncomfortable with the deep, deep magic that dynamic wrappers have to resort to to create new entry points at runtime. Since I'm registering a static top-level function, I shouldn't be having any of these problems. And indeed, I can get a FunPtr for the function... by exporting it first:
foreign export ccall "my_callback" myCallback :: IO () foreign import ccall "&my_callback" myCallbackPtr :: FunPtr (IO ()) registerMy' :: IO () registerMy' = registerCallback myCallbackPtr
So this works, but it's annoying. I need to write redundantly two almost similar-looking foreign declarations, and this gives the impression of a strange hack instead of a normal conversion. Worst of all, I'm forced to pollute the symbol namespace by exporting my function as a symbol with external linkage. But I don't need my callback to be visible as a symbol to foreign code! I just need its address so I can pass it to the registration function. This is a very minor thing, but this seems like a very common use case so it's strange that there doesn't seem to be direct support for it. Is there really no way to tell the compiler to create a _static_ stub for a Haskell function and return the address of that stub, but _not_ export it as a symbol? Thanks, Lauri _______________________________________________ FFI mailing list [email protected] http://www.haskell.org/mailman/listinfo/ffi
