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

Brian Hulley brianh at metamilk.com
Wed Mar 15 11:44:55 EST 2006


kahl at cas.mcmaster.ca wrote:
> 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}

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. 



More information about the Glasgow-haskell-users mailing list