Passing arrays between Haskell and C without overhead

Brian Hulley brianh at metamilk.com
Sun Nov 26 09:34:51 EST 2006


Hi,

For a 3d graphics library, I'd like to have a 4x4 matrix of floats which I 
can pass from Haskell to C without having to copy all 16 floats each time, 
something like:

    data Mat44f = Mat44f Float# Float# ... Float#

    foreign import ccall c_setWorldTransform :: Ptr Mat44f -> IO ()

    setWorldTransform :: Mat44f -> IO ()
    setWorldTransform mat =
        withSafePtr mat c_setWorldTransform

where

    withSafePtr :: a -> (Ptr a -> IO b) -> IO b

would supply a pointer directly to the Haskell heap representation of (a) 
and would ensure that (a) doesn't get garbage collected until the IO action 
is completed. (Note that this is not the same as Foreign.Marshal.Utils.with, 
which uses alloca and poke to copy the matrix - I'm trying to avoid this 
overhead of copying.)

However there is no such function afaics so the only solutions at present 
seem to be to either make Mat44f an instance of Storable and use alloca 
(which involves copying all 16 floats just so that C can read it even though 
I'd expect the heap representation to already be identical since there is 
only one constructor and all fields are unboxed) or else pass the 16 floats 
individually by:

    foreign import ccall c_SetWorldTransform' :: Float# -> Float# -> ... -> 
Float# -> IO ()

    setWorldTransform (Mat44f m11 m12 m13 m14 ... m44) =
        c_SetWorldTransform' m11 m12 m13 ... m44

In this second case the C function will have to manually put these 16 floats 
back into an array so that it will have a pointer to a temporary array of 16 
floats to use internally (eg to pass to the DirectX api which will then make 
its own copy of it), so in both cases there is a wasteful deconstruction 
then reconstruction of the original array of 16 floats stored on the Haskell 
heap.

Similar problems arise when trying to pass an array from C back to Haskell, 
but in this case it's clear some copying will be needed so that one ends up 
with a value stored on the Haskell heap - the "double copy" problem only 
arises in the direction from Haskell to C.

I've also thought about just implementing all the math functions in C and 
using mallocForeignPtrArray so that the data type would be:

    newtype Mat44f = Mat44f (ForeignPtr CFloat)

While this would make passing between C and Haskell very fast, it seems a 
pity to have to sacrifice the ability to code the math ops directly in 
Haskell in a functional style with all the attendant optimizations one could 
expect from GHC (using ForeignPtr requires unsafePerformIO, withForeignPtr, 
and lots and lots of peek/pokeElemOff's in a monadic style - rather gross 
compared to pattern matching etc)

So my questions are:

1) Is there any reason why there can't be a function (withSafePtr) to avoid 
all this marshalling overhead when we know (or specify via a pragma) that 
Haskell stores the data already in a form compatible with C, or is there 
some other way to represent a 4x4 matrix such that it can be manipulated in 
Haskell and passed without overhead to C?

2) Does withSafePtr already exist somewhere?

3) Would it be a good idea to make Storable one of the classes which can be 
automatically derived?

Thanks, Brian.
-- 
http://www.metamilk.com 



More information about the Glasgow-haskell-users mailing list