Let's get this finished

Manuel M. T. Chakravarty chak at cse.unsw.edu.au
Wed Jan 10 21:10:34 EST 2001


Simon Marlow <simonmar at microsoft.com> wrote,

> > Granted. And remember we already have a (quite ugly) module CString!
> > So here is a new proposal:
[..]
> Ok.  I'm still using the existing CString, but it can be renamed to
> something else.  I've been using "UnsafeCString" since these ByteArray
> CStrings can only be passed to unsafe foreign functions.  For now, let's
> just rename CString to UnsafeCString and change all the uses.

George Russell <ger at tzi.de> wrote,

> The current UniForM sources use both PackedString and CString in various
> places.  The interface to PackedString happens to be documented, which was
> why I thought it might be possible to rely on it.

So far, I have simply deprecated the use of the old
functions in CString (in fact only those that are actually
defined in CString, not those re-exported from other
places).  So, nothing should break.

I am all for moving the old CString routines to
UnsafeCString, but that might annoy George and others who
still have code importing the old CString.

The old code contains cruft like

    fill arr n [] =
	_casm_ ``((PP_)%0)[%1] = NULL;'' arr n
    fill arr n (x:xs) = do
	barr <- packStringIO x
        _casm_ ``((PP_)%0)[%1] = (P_)%2;'' arr n barr
	fill arr (n+1) xs

which doesn't make much sense keeping around with the new
FFI stuff in place.

As 4.08.2 will still have the old interfaces, one possible
route might be a more radical step for the first GHCi
release (which will break all kinds of things anyway, I am
sure :-}  We could collect all the old interfaces (I guess,
there are other modules beside CString that can be phased
out) in a new module "LangDeprecated" where we maybe even
redefine the old routines in terms of the new ones.  Code
using the old interfaces can, then, just import
LangDeprecated until the code gets revised, but it is clear
that the old interfaces will vanish one day.

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*

Cheers,
Manuel




More information about the FFI mailing list