Let's get this finished

Simon Marlow simonmar at microsoft.com
Thu Jan 4 05:59:05 EST 2001


> MarshalUtils
> ~~~~~~~~~~~~
> The reason that I don't like MarshalUtils as it is are the
> following:
> 
> (1) It isn't H98 and in fact its interface cannot be
>     implemented with H98[1].  The problem are the routines
>     with signatures in patterns:
> 
>       malloc :: Storable a => IO (Ptr a)
>       malloc :: IO (Ptr a) = mallocBytes (sizeOf (undefined::a))
> 
>       alloca :: Storable a => (Ptr a -> IO b) -> IO b
>       alloca (act :: Ptr a -> IO b) = allocaBytes (sizeOf 
> (undefined::a)) act
> 
>       <etc>

How about this:

	malloc :: Storable a => IO (Ptr a)
	malloc = res
	  where res = mallocBytes (sizeOf (unsafePerformIO
(res>>=peek)))

:-)

The result type signatures are just a convenient (and much more
readable) way to write these functions.

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

Ok.  Actually I consider the current libraries to be on the verge of
usability, modulo the missing string marshalling and error
functionality.

> The Marshal modules
> ~~~~~~~~~~~~~~~~~~~
> I propose the following set of modules:
> 
> - MarshalAlloc: 
>     The allocation routines that are in MarshalUtils now,
>     but modified as outlined above.
> 
> - MarshalArray: 
>     The array marshalling routines
> 
> - MarshalString: 
>     Most people seem to be of the opinion that we have to
>     handle strings specially due to Unicode conversion
>     requirements.  So, this is were string marshalling goes.

I've been wondering whether we should have something like

	newtype CString = CString (Ptr CChar)

which would allow GHC to replace the representation with a ByteArray
leading to a much more efficient implementation of withCString.  There
are other reasons why having a special CString type might be a good
idea: a C string really is more than just a pointer to char, it is an
array with a zero terminator and is specified in some kind of encoding.
Having a special CString type would provide more type safety.

One problem with the optimisation is that GHC can't handle ByteArrays
being *returned* from a foreign function.

> - MarshalError: 
>     Combinators to test for common error conditions.  The
>     main open problem here is the handling of errno, I
>     think. 
> 
> - MarshalConv: 
>     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.

Could you explain the motivation for these?  I can see the need for some
way to convert Bool<=>CInt (which is defined by ISO C), but can't the
others be just fromIntegral?

> Moreover,
>     soemthing along the C2HS ToAddr/FromAddr classes, but it
>     probably makes to have `stdArrayPtr' etc as additional
>     member functions (this is similar to the newXXX routines
>     that are in MarshalUtils now, but with additional
>     overloading).  Furthermore, Marcin-syle withXXX routines
>     would fo here.

I'm not sure how ToAddr/FromAddr would work.  From looking at C2HS, they
seem to provide a consistent interface to marshalling that is specific
to a given Haskell type.  I haven't found a need for something like this
in my own code yet, so again could you motivate?

> - MarshalUtils: 
>     The memcpy/memmove stuff, indexPtr (if it still makes
>     sense), and whatever else doesn't get its own module.
> 
> I think, we should leave C2HS's marshX routines out.  We
> discussed how to make them arity independent for quite a
> while and AFAIR, there wasn't a really good proposal.
> Finally, all the above modules should be jointly exported by
> a module `Marshal'.

Sounds fine.

Cheers,
	Simon




More information about the FFI mailing list