"Manuel M. T. Chakravarty" wrote:
> I wouldn't call autoconf a hack :-)
OK, MEGA-hack. :-) But it's m4 which is the real culprit...
> [...] Anyway, such a class seems to be a nice way for expressing
> the information about marshalable data types.
The class is actually more about "micro"-marshaling, e.g. there are no
methods which actually do some form of memory management. In my current
OpenGL-binding I actually use the following larger class definition:
---------------------------------------------------------------------
class Eq a => Marshalable a where
sizeOf :: a -> Int
zeroElem :: a
indexOffAddr :: Addr -> Int -> a
readOffAddr :: Addr -> Int -> IO a
writeOffAddr :: Addr -> Int -> a -> IO ()
marshal :: a -> IO Addr
marshalList :: [a] -> IO Addr
marshalListZero :: [a] -> IO Addr
unmarshal :: Addr -> IO a
unmarshalList :: Int -> Addr -> IO [a]
unmarshalListZero :: Addr -> IO [a]
marshal x = marshalList [x]
marshalList xs = do
buf <- malloc (length xs * sizeOf (head xs))
zipWithM_ (writeOffAddr buf) [ 0 .. ] xs
return buf
marshalListZero xs = do
let numElements = length xs
buf <- malloc ((numElements+1) * sizeOf (head xs))
zipWithM_ (writeOffAddr buf) [ 0 .. ] xs
writeOffAddr buf numElements (zeroElem `asTypeOf` head xs)
return buf
unmarshal buf = liftM head $ unmarshalList 1 buf
unmarshalList numElements buf =
mapM (readOffAddr buf) [ 0 .. numElements-1 ]
unmarshalListZero buf = loop 0 []
where loop idx accu = do x <- readOffAddr buf idx
if x == zeroElem
then return $ reverse accu
else loop (idx+1) (x:accu)
---------------------------------------------------------------------
This captures usual marshaling/unmarshaling patterns for
* a single value,
* a list of values,
* and a list of values, terminated by a special value (zeroElem).
Two typical instances are:
---------------------------------------------------------------------
instance Marshalable Char where
sizeOf = const @ac_cv_sizeof_char@
zeroElem = '\0'
indexOffAddr = indexCharOffAddr
readOffAddr = readCharOffAddr
writeOffAddr = writeCharOffAddr
instance Marshalable Addr where
sizeOf = const @ac_cv_sizeof_void_p@
zeroElem = nullAddr
indexOffAddr = indexAddrOffAddr
readOffAddr = readAddrOffAddr
writeOffAddr = writeAddrOffAddr
---------------------------------------------------------------------
The @ac_cv_sizeof_...@ are substituted by the configure script.
Given the above class definition one can write convenient higher order
functions, e.g. for in/inout parameter passing (which actually
involve some kind of alloca):
---------------------------------------------------------------------
inParamWith :: (a -> IO Addr) -> (Addr -> IO b) -> a -> IO b
inParamWith marsh act x = do
buf <- marsh x
ret <- act buf
free buf
return ret
inParam :: Marshalable a => (Addr -> IO b) -> a -> IO b
inParam = inParamWith marshal
inOutParamWith :: (a -> IO Addr) -> (Addr -> IO a) -> (Addr -> IO ()) -> a -> IO a
inOutParamWith marsh unmarsh act x = do
buf <- marsh x
act buf
ret <- unmarsh buf
free buf
return ret
inOutParam :: Marshalable a => (Addr -> IO ()) -> a -> IO a
inOutParam = inOutParamWith marshal unmarshal
---------------------------------------------------------------------
I know Manuel's code already and the one H/Direct produces. Has
anybody else some FFI-related code and/or suggestions? This could be
a wonderful topic for the wish list, but it would be nice to see the
problems and needs for APIs different from GTK+ and OpenGL first.
Cheers,
Sven
P.S. for the native speakers: Which spelling is correct, "marshaling"
or "marshalling"? Ispell says "marshaling", but this looks a bit odd
to me.
--
Sven Panne Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED] D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne