ForeignPtr's - why can't they be passed directly to foreign
functions?
kahl at cas.mcmaster.ca
kahl at cas.mcmaster.ca
Wed Mar 15 10:40:38 EST 2006
Brian Hulley <brianh at metamilk.com> 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}
>
> 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
More information about the Glasgow-haskell-users
mailing list