ForeignPtr's - why can't they be passed directly to foreign functions?

Hi - I've got the beginnings of an API for a GUI system as follows: data DWindow a data DEdit a type Window = DWindow type Edit a = DWindow (DEdit a) foreign import ccall duma_init :: IO () foreign import ccall duma_run :: IO () foreign import ccall duma_release :: FunPtr (Ptr (Window a) -> IO ()) foreign import ccall duma_createEdit :: IO (Ptr (Edit a)) foreign import ccall duma_addTop :: Ptr (Window a) -> IO () createEdit :: IO (ForeignPtr (Edit a)) createEdit = do edit <- duma_createEdit newForeignPtr duma_release edit addTop :: ForeignPtr (Window a) -> IO () addTop w = withForeignPtr w duma_addTop This works, but it seems a bit of a pain to have to manually convert between ForeignPtr's and Ptr's all the time. In particular, for the definition of addTop, I tried: foreign import ccall "duma_addTop" addTop :: ForeignPtr (Window a) -> IO () but got an error because ForeignPtr's are not allowed as part of the type of a foreign function. Since the definition of ForeignPtr is just void *, I wonder why this restriction exists - ie is a ForeignPtr not just the same address as the corresponding Ptr? My other question is what happens if I want to have a function that takes more than one ForeignPtr as argument ie foreign import ccall duma_test :: Ptr (Window a) -> Ptr (Window a) -> IO () test :: ForeignPtr (Window a) -> ForeignPtr (Window a) -> IO () test p q = withForeignPtr p (\p' -> withForeignPtr q $ duma_test p') Is this the only way to achieve this? It seems a bit long-winded and possibly a bit inefficient... One other question: if I use forkIO within Haskell, am I right in thinking that the lightweight concurrent threads are safe to use with my single threaded C code ie that there is no danger of a thread being preemptively halted while it is inside a foreign function? Thanks, Brian.

On 3/15/06, Brian Hulley
Hi - I've got the beginnings of an API for a GUI system as follows:
data DWindow a data DEdit a
type Window = DWindow type Edit a = DWindow (DEdit a)
foreign import ccall duma_init :: IO () foreign import ccall duma_run :: IO ()
foreign import ccall duma_release :: FunPtr (Ptr (Window a) -> IO ())
foreign import ccall duma_createEdit :: IO (Ptr (Edit a)) foreign import ccall duma_addTop :: Ptr (Window a) -> IO ()
createEdit :: IO (ForeignPtr (Edit a)) createEdit = do edit <- duma_createEdit newForeignPtr duma_release edit
(Not directly related, but maybe useful to know) Stricly speaking, asynchronous exception may occur in between, and this code should in fact be "surrounded" by block to prevent resource leaks. createEdit = block $ do edit <- duma_createEdit newForeignPtr duma_release edit
addTop :: ForeignPtr (Window a) -> IO () addTop w = withForeignPtr w duma_addTop
This works, but it seems a bit of a pain to have to manually convert between ForeignPtr's and Ptr's all the time. In particular, for the definition of addTop, I tried:
foreign import ccall "duma_addTop" addTop :: ForeignPtr (Window a) -> IO ()
but got an error because ForeignPtr's are not allowed as part of the type of a foreign function. Since the definition of ForeignPtr is just void *, I wonder why this restriction exists - ie is a ForeignPtr not just the same address as the corresponding Ptr?
First, Ptr and ForeignPtr are totally diffrent beasts. Ptr is just plain address, while ForeignPtr might have associated finalisers. When Ptr is garbage collected, there is nothing diffrent from collecting other simple types. Just throw the (as an implementation detail) the integer holding address away. When ForeignPtr is garbage collected, the finaliser must be run (or scheduled to run). which requires extra bookkeeping and quite a bit of work on part of runtime. In short: it could be handled as you like. (I think - just need ForeignPtr to C pointer conversion and guarantee ForeignPtr won't die while in ffi call) Reality: There is no magic in ForeignPtr for ffi calls, and hence it's just like any other haskell object (like any other boxed value, anyway) - the parameter given to the function might be last reference to the value, and it might be optimised/thrown away just before the actual function call, get garbage collected and resource might be free'd. Which certainly isn't what you want.
My other question is what happens if I want to have a function that takes more than one ForeignPtr as argument ie
foreign import ccall duma_test :: Ptr (Window a) -> Ptr (Window a) -> IO ()
test :: ForeignPtr (Window a) -> ForeignPtr (Window a) -> IO () test p q = withForeignPtr p (\p' -> withForeignPtr q $ duma_test p')
Is this the only way to achieve this? It seems a bit long-winded and possibly a bit inefficient...
I would like to know answer to this question as well. I quite often would like to have an framework to handle (ffi) resource in more convient manner. Typically, I write few simple combinators for with-style functions. If not, using $ might make code nicer than (). withForeignPtr foo $ \foo -> withForeignPtr bar $ \bar -> do use foo use bar return baz I haven't tried if there is a big performance loss from multiple nested block and unblock calls those with-functions require. If there is, a framework could actually be optimised.
One other question: if I use forkIO within Haskell, am I right in thinking that the lightweight concurrent threads are safe to use with my single threaded C code ie that there is no danger of a thread being preemptively halted while it is inside a foreign function?
If I understand correctly, GHC RTS won't halt the thread while it's performing ffi call. HTH, -Esa

Esa Ilari Vuokko wrote:
On 3/15/06, Brian Hulley
wrote: [snip]
(Not directly related, but maybe useful to know) Stricly speaking, asynchronous exception may occur in between, and this code should in fact be "surrounded" by block to prevent resource leaks.
createEdit = block $ do edit <- duma_createEdit newForeignPtr duma_release edit
Thanks for pointing this out. I also realised it is simpler to write using
= as:
createEdit = block $ duma_createEdit >>= newForeignPtr duma_release
In particular, for the definition of addTop, I tried:
foreign import ccall "duma_addTop" addTop :: ForeignPtr (Window a) -> IO ()
but got an error because ForeignPtr's are not allowed as part of the type of a foreign function. Since the definition of ForeignPtr is just void *, I wonder why this restriction exists - ie is a ForeignPtr not just the same address as the corresponding Ptr?
First, Ptr and ForeignPtr are totally diffrent beasts. Ptr is just plain address, [snip] Reality: There is no magic in ForeignPtr for ffi calls, and hence it's just like any other haskell object (like any other boxed value, anyway) - the parameter given to the function might be last reference to the value, and it might be optimised/thrown away just before the actual function call, get garbage collected and resource might be free'd. Which certainly isn't what you want.
I'd forgotten that Haskell function calls are quite different to C (where temp objects for example always survive till the call returns since C doesn't have tail call optimization) Thanks, Brian.

Brian Hulley
My other question is what happens if I want to have a function that takes more than one ForeignPtr as argument ie
foreign import ccall duma_test :: Ptr (Window a) -> Ptr (Window a) -> IO ()
test :: ForeignPtr (Window a) -> ForeignPtr (Window a) -> IO () test p q = withForeignPtr p (\p' -> withForeignPtr q $ duma_test p')
Is this the only way to achieve this? It seems a bit long-winded and possibly a bit inefficient...
I use: \begin{code} {-# INLINE with2ForeignPtrs #-} {-# INLINE with3ForeignPtrs #-} with2ForeignPtrs :: ForeignPtr a -> ForeignPtr b -> (Ptr a -> Ptr b -> IO c) -> IO c with2ForeignPtrs f1 f2 m = withForeignPtr f1 (withForeignPtr f2 . m) \end{code} \begin{code} with3ForeignPtrs :: ForeignPtr a -> ForeignPtr b -> ForeignPtr c -> (Ptr a -> Ptr b -> Ptr c -> IO d) -> IO d with3ForeignPtrs f1 f2 f3 m = withForeignPtr f1 (with2ForeignPtrs f2 f3 . m) \end{code}
foreign import ccall duma_init :: IO ()
^^^^ Any relation with duma.sourceforge.net ? ``D.U.M.A. - Detect Unintended Memory Access'' We just used that for hunting down memory leaks in a C library we produced an FFI binding to... Wolfram

kahl@cas.mcmaster.ca wrote:
Brian Hulley
wrote: My other question is what happens if I want to have a function that takes more than one ForeignPtr as argument ie
foreign import ccall duma_test :: Ptr (Window a) -> Ptr (Window a) -> IO ()
test :: ForeignPtr (Window a) -> ForeignPtr (Window a) -> IO () test p q = withForeignPtr p (\p' -> withForeignPtr q $ duma_test p')
Is this the only way to achieve this? It seems a bit long-winded and possibly a bit inefficient...
I use:
\begin{code} {-# INLINE with2ForeignPtrs #-} {-# INLINE with3ForeignPtrs #-} with2ForeignPtrs :: ForeignPtr a -> ForeignPtr b -> (Ptr a -> Ptr b -> IO c) -> IO c with2ForeignPtrs f1 f2 m = withForeignPtr f1 (withForeignPtr f2 . m) \end{code}
\begin{code} with3ForeignPtrs :: ForeignPtr a -> ForeignPtr b -> ForeignPtr c -> (Ptr a -> Ptr b -> Ptr c -> IO d) -> IO d with3ForeignPtrs f1 f2 f3 m = withForeignPtr f1 (with2ForeignPtrs f2 f3 . m) \end{code}
Good idea!
foreign import ccall duma_init :: IO ()
^^^^
Any relation with duma.sourceforge.net ? ``D.U.M.A. - Detect Unintended Memory Access''
No - I just got it off the cover of a DVD! (after spending about a week wasting time trying to think of a name... :-) ) Thanks, Brian.

Brian Hulley wrote:
I've got the beginnings of an API for a GUI system as follows: ... addTop :: ForeignPtr (Window a) -> IO () addTop w = withForeignPtr w duma_addTop
This works, but it seems a bit of a pain to have to manually convert between ForeignPtr's and Ptr's all the time. In particular, for the definition of addTop, I tried:
foreign import ccall "duma_addTop" addTop :: ForeignPtr (Window a) -> IO ()
This is the way it used to be in GHC before the FFI. In the FFI we moved to withForeignPtr instead. IIRC, the motivation was something along these lines: - allowing ForeignPtr to be passed directly to a foreign function implies some magic that happens at the point of the foreign call to convert the ForeignPtr to a Ptr. - there also has to be some magic to ensure that the ForeignPtr couldn't be finalized until the call returns. This amounted to adding a touch# primitive to keep the ForeignPtr alive over the call. So internally the compiler was doing something like withForeignPtr anyway. This behaviour is quite hard to explain in the spec, withForeignPtr is much simpler. - We wanted withForeignPtr anyway, to avoid having to duplicate all the marshalling operations that operate on Ptr. So, given that we wanted withForeignPtr anyway, there was no need to also have the compiler do its internal magic to allow ForeignPtr to be used as an FFI argument. Also, this means GHC doesn't need a primitive ForeignPtr type (the primitive Ptr type is enough). Later on, we discovered that the withForeignPtr interface enables a much more efficient representation of ForeignPtr. This is coming in GHC 6.6. Cheers, Simon

Simon Marlow wrote:
Brian Hulley wrote:
I've got the beginnings of an API for a GUI system as follows: ... addTop :: ForeignPtr (Window a) -> IO () addTop w = withForeignPtr w duma_addTop
This works, but it seems a bit of a pain to have to manually convert between ForeignPtr's and Ptr's all the time. In particular, for the definition of addTop, I tried:
foreign import ccall "duma_addTop" addTop :: ForeignPtr (Window a) -> IO ()
This is the way it used to be in GHC before the FFI. In the FFI we moved to withForeignPtr instead. IIRC, the motivation was something along these lines:
- allowing ForeignPtr to be passed directly to a foreign function implies some magic that happens at the point of the foreign call to convert the ForeignPtr to a Ptr.
- there also has to be some magic to ensure that the ForeignPtr couldn't be finalized until the call returns. This amounted to adding a touch# primitive to keep the ForeignPtr alive over the call. So internally the compiler was doing something like withForeignPtr anyway. This behaviour is quite hard to explain in the spec, withForeignPtr is much simpler.
The above two things were what I was expecting the compiler to do for me instead of me having to manually write a wrapper function in Haskell using withForeignPtr for each wrapper function for each foreign function...
- We wanted withForeignPtr anyway, to avoid having to duplicate all the marshalling operations that operate on Ptr.
So, given that we wanted withForeignPtr anyway, there was no need to also have the compiler do its internal magic to allow ForeignPtr to be used as an FFI argument. Also, this means GHC doesn't need a primitive ForeignPtr type (the primitive Ptr type is enough).
Would it be possible to just treat ForeignPtr in foreign types as syntactic sugar ie foreign import ccall foo :: ForeignPtr a -> IO () would just be syntactic sugar for: foreign import ccall "foo" foo' :: Ptr a -> IO () foo :: ForeignPtr a -> IO () foo x = withForeignPtr x foo' The re-writing could be done at an early stage so that you'd still only need to deal with marshalling Ptr, but would save the user from having to manually create these extra wrappers, and would also give a simple way of explaining the meaning of a ForeignPtr argument in a foreign function type.
Later on, we discovered that the withForeignPtr interface enables a much more efficient representation of ForeignPtr. This is coming in GHC 6.6.
Every cloud has a silver lining! :-))) Thanks, Brian.

On Wed, 2006-03-15 at 17:01 +0000, Brian Hulley wrote:
Simon Marlow wrote:
This is the way it used to be in GHC before the FFI. In the FFI we moved to withForeignPtr instead. IIRC, the motivation was something along these lines:
- allowing ForeignPtr to be passed directly to a foreign function implies some magic that happens at the point of the foreign call to convert the ForeignPtr to a Ptr.
- there also has to be some magic to ensure that the ForeignPtr couldn't be finalized until the call returns. This amounted to adding a touch# primitive to keep the ForeignPtr alive over the call. So internally the compiler was doing something like withForeignPtr anyway. This behaviour is quite hard to explain in the spec, withForeignPtr is much simpler.
The above two things were what I was expecting the compiler to do for me instead of me having to manually write a wrapper function in Haskell using withForeignPtr for each wrapper function for each foreign function...
This is exactly the sort of thing that FFI tools automate. Indeed they can do this and much more. Duncan

Am Mittwoch, 15. März 2006 18:16 schrieb Duncan Coutts:
On Wed, 2006-03-15 at 17:01 +0000, Brian Hulley wrote:
The above two things were what I was expecting the compiler to do for me instead of me having to manually write a wrapper function in Haskell using withForeignPtr for each wrapper function for each foreign function...
This is exactly the sort of thing that FFI tools automate. Indeed they can do this and much more.
Duncan is right here: Our design goal when specifying the FFI was to define only those mechanisms which are absolutely necessary to interface to foreign languages. Everything which doesn't need any help from the compiler/RTS is explicitly left to higher-level tools. The only real redundancy AFAIK is the fact the newtypes are "transparent" to the FFI, but this is extremely handy and improves type safety and readability quite a bit. I admit being guilty for having insisted on that non-minimalistic feature, but I'm proud of it... ;-) Cheers, S.

Brian Hulley wrote:
Hi - I've got the beginnings of an API for a GUI system as follows:
foreign import ccall duma_createEdit :: IO (Ptr (Edit a))
createEdit :: IO (ForeignPtr (Edit a))
These should of course be: foreign import ccall duma_createEdit :: IO (Ptr (Edit ())) and createEdit :: IO (ForeignPtr (Edit ())) (just in case anyone else new to phantom types reads this email before writing a GUI) Regards, Brian.
participants (6)
-
Brian Hulley
-
Duncan Coutts
-
Esa Ilari Vuokko
-
kahl@cas.mcmaster.ca
-
Simon Marlow
-
Sven Panne