Let's get this finished

Manuel M. T. Chakravarty chak at cse.unsw.edu.au
Sun Jan 14 09:56:55 EST 2001


Simon Marlow <simonmar at microsoft.com> wrote,

> Most uses of unpackCString and friends can be replaced with peekCString
> (CStrings from a foreign function are bound to be Ptr CChar).  For
> packString, I've been using the following interface instead (in
> ghc/lib/std/PrelCString):
> 
> 	data UnsafeCString
> 	withUnsafeCString :: String -> (UnsafeCString -> IO a) -> IO a
> 
> where an UnsafeCString is valid only in an argument position of an
> unsafe foreign import.
> 
> Would anyone object to adding these to CString?

Fine by me, but IMHO we should really have similar routines
for other types of objects, too.

> > Moreover, as soon as the unicode stuff gets in, all the old
> > C-style string handling will be wrong anyway.
> > 
> > As for bytearrays: AFAIK the only reason for using byte
> > arrays over malloc is efficiency.  So, that makes them, I
> > think, mainly interesting for allocating temporary storage,
> > which is maybe even more critical for routines that need
> > pointers to storage as out parameters to C routines doing
> > little work.  This is actually more critical for routines
> > handling small data items like ints than for strings.  So,
> > we would like to have something like
> > 
> >   with[Object]Unsafe   :: Storable a => a -> (Ptr a -> IO b) -> IO b
> >   withArrayUnsafe      :: Storable a =>      [a] -> (Ptr a -> 
> > IO b) -> IO b
> >   withArray0Unsafe     :: Storable a => a -> [a] -> (Ptr a -> 
> > IO b) -> IO b
> >   withCStringUnsafe    :: String -> (CString -> IO a) -> IO a
> >   withCStringLenUnsafe :: String -> (CStringLen -> IO a) -> IO a
> > 
> > However, the real problem here is that if we want to use
> > `ByteArray' instead of `Ptr', the types have to change and
> > it is not H98 anymore.  So, the problem is getting the
> > pointer from the allocation to the C function without moving
> > it. *sigh*
> 
> I still can't think of a good way to do this in general.  Perhaps
> enhancing the garbage collector so that it could "pin" objects - but
> you've still got the problem of keeping the lifetime of the ByteArray in
> sync with the Ptr.

Can't we touch# the ByteArray until the function passed to
the with combinator returns?  That should do the trick.

Cheers,
Manuel




More information about the FFI mailing list