"Marcin 'Qrczak' Kowalczyk" <[EMAIL PROTECTED]> wrote,
> 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)
Cool! You are right, I completely forgot about local type
declarations. That's good, your signatures are definitelty
nicer.
> IMHO MarshalUtils exported by Foreign is the right place for it.
> But I don't care how functions will be split into modules.
If we put everything into MarshalUtils it will get too big.
So, why not structure it a bit, as we did with the other FFI
modules, too.
> String handling will be needed. It would be silly to provide strings but
> not provide arrays in general.
Sure, but as you pointed out: Strings are special, but
internally rely on the array routines. So it makes sense,
to have a module with the general arrays stuff plus an extra
module with the special string handling.
> > 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.
Ok, I can change this.
> 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.
But if it occurs repeatedly, it is much nicer to have a
function (mind you, the whole high-level libraries is only
about convenience anyway).
> 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).
I don't much like having explicit constants all over the
place - especially because everybody will put 1 and 0 in the
wrong order half the time.
Cheers,
Manuel
_______________________________________________
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi