Let's get this finished

Marcin 'Qrczak' Kowalczyk mk167280 at students.mimuw.edu.pl
Thu Jan 4 04:36:01 EST 2001


On Thu, 4 Jan 2001, Manuel M. T. Chakravarty wrote:

> (1) It isn't H98 and in fact its interface cannot be
>     implemented with H98[1].

It can.

>       malloc :: Storable a => IO (Ptr a)
>       malloc :: IO (Ptr a) = mallocBytes (sizeOf (undefined::a))

malloc :: Storable a => IO (Ptr a)
malloc = malloc' undefined
    where
    malloc' :: Storable a => a -> IO (Ptr a)
    malloc' undef = mallocBytes (sizeOf undef)

>       alloca :: Storable a => (Ptr a -> IO b) -> IO b
>       alloca (act :: Ptr a -> IO b) = allocaBytes (sizeOf (undefined::a)) act

alloca :: Storable a => (Ptr a -> IO b) -> IO b
alloca = alloca' undefined
    where
    alloca' :: Storable a => a -> (Ptr a -> IO b) -> IO b
    alloca' undef = allocaBytes (sizeOf undef)

> (2) pokeArray, peekArray, etc are really part of what should
>     go into the high-level marshalling.

IMHO MarshalUtils exported by Foreign is the right place for it.
But I don't care how functions will be split into modules.

String handling will be needed. It would be silly to provide strings but
not provide arrays in general.

>     The C2HS IntConv, BoolConv, etc classes.  Marcin just
>     uses `fromIntegral' here, but I think that this is too
>     limited - eg, it doesn't handle Bool.

You handle Bool by converting True to -1. I think that most libraries
would expect 1 as True. Anyway, IMHO it's ok to leave this out, because
it's easy to write (/= 0) in one direction, and (\b -> if b then 1 else 0)
in the other.

Well, for the latter it could make sense to provide a function which is
related to Bool as maybe is related to Maybe. It's a plain if with
a different order of arguments:
    bool :: a -> a -> Bool -> a
    -- Or the name cond might be better.
Then the conversion from Bool is: bool 1 0. Or bool 0 1. I'm not sure
which order is better (false true: consistent with maybe and ordering
on Bool, true false: consistent with plain if).

-- 
Marcin 'Qrczak' Kowalczyk





More information about the FFI mailing list