GreenCard: list marshalling
Alastair Reid
reid@cs.utah.edu
03 Jun 2002 12:43:52 +0100
> Hi, I'd like to call LaPack routines from Haskell.
> Having read the GreenCard documentation it's still not obvious to me
> how I could marshall a list of numbers to C. Surely it's possible
> to create a ForeignObj, then fill it in element-by- element. But
> isn't there a more straightforward way? Even without monads?
Here's some code from the Xlib interface: hslibs/xlib/Xlib.gc
(This code is part of the HGL (http://haskell.org/graphics).)
First, a function that wants a list of objects.
Note that we use ListPoint (a type synonym we'll define below) instead
of [Point]. The name 'ListPoint' triggers the appropriate kind of
marshalling.
Note too that the %call line contains:
(listPoint arg4 arg4_size)
That is, listPoint marshalling results in 2 arguments to the C function.
> %fun XDrawPoints :: Display -> Drawable -> GC -> ListPoint -> CoordinateMode -> IO ()
> %call (display arg1) (drawable arg2) (gC arg3) (listPoint arg4 arg4_size) (coordinateMode arg5)
> %code XDrawPoints(arg1,arg2,arg3,arg4,arg4_size,arg5)
> %end free(arg4)
Marshalling lists of points uses the functions marshallAddrList and
unmarshallAddrList (defined later).
> type ListPoint = [Point]
> %dis listPoint x l = <<marshallAddrList allocPoints writePoint/unmarshallAddrList readPoint>> (addr ({XPoint*} x)) (int l)
To marshall a list of points we have to allocate some space in the C heap.
Note that the size is scaled by the size of the objects.
> %fun allocPoints :: Int -> IO Addr
> %code res1 = (void*)malloc(sizeof(XPoint) * arg1)
write points into an array
> %fun writePoint :: Addr -> Int -> Point -> IO ()
> %call (addr ({XPoint*} s)) (int i) (point {s[i]})
> %code
and read points from an array
> %fun readPoint :: Addr -> Int -> IO Point
> %call (addr ({XPoint*} s)) (int i)
> %code
> %result (point {s[i]})
These functions are useful with many different types of list.
To marshall we:
1) Get the list length
2) Allocate an array that size in the C heap
3) Write values into the array.
> marshallAddrList :: (Int -> IO Addr) -> (Addr -> Int -> a -> IO ()) -> [a] -> IO (Addr, Int)
> marshallAddrList alloc write as = do
> let l = length as
> arr <- alloc l
> zipWithM_ (write arr) [0..] as
> return (arr, l)
To unmarshall we read values out.
Freeing the array could be done here too but in this case it happens
in the %end of the %fun that uses the array. It's a long time since I
wrote this code so I can only guess that I thought this way would be
more flexible.
> unmarshallAddrList :: (Addr -> Int -> IO a) -> (Addr, Int) -> IO [a]
> unmarshallAddrList read (ptr,l) = mapM (read ptr) [0..l-1]
Points are defined in the usual way. I won't discuss this much since
I think you just want Int or Floats or some such.
> type Point =
> ( Position -- x
> , Position -- y
> )
> %dis point x = declare {XPoint} x in
> % ( position {(%x).x}
> % , position {(%x).y}
> % )
Hope this helps,
--
Alastair Reid reid@cs.utah.edu http://www.cs.utah.edu/~reid/