ANN: H98 FFI Addendum 1.0, Release Candidate 7

Manuel M T Chakravarty chak at cse.unsw.edu.au
Mon Sep 23 21:25:27 EDT 2002


Ross Paterson <ross at soi.city.ac.uk> wrote,

> On Sun, Sep 22, 2002 at 02:54:44PM +1000, Manuel M T Chakravarty wrote:
> > Ross Paterson <ross at soi.city.ac.uk> wrote,
> > 
> > > Alastair Reid <alastair at reid-consulting-uk.ltd.uk> wrote:
> > > > I guess the issue is that if someone wanted to use MarshalAlloc.free
> > > > as a finalizer they would not be able to do so.  Since we don't
> > > > guarantee that MarshalAlloc.malloc is "stdio.h malloc", they couldn't 
> > > > portably cons up a compatible &free.
> > > 
> > > Yes, you're trying to recover something that was lost with the change
> > > to newForeignPtr.  Formerly one could allocate something with malloc
> > > or mallocArray and add a finalizer that called free.  Now you can't,
> > > except in the canned special case of mallocForeignPtr.  But there's
> > > nothing similar for arrays, as required e.g. in Data.Array.Storable.
> > 
> > I think SimonM and Ross have a point here.  There isn't
> > really anything gained from linking `MarshalAlloc.malloc' up
> > with a C version of `MarshalAlloc.free'.  So, I think we
> > should leave it as it is.
> 
> That wasn't what I was arguing.  Consider the following code from
> Data.Array.Storable:
> 
>     newArray_ (l,u) = do
>         a  <- mallocArray (rangeSize (l,u))
>         fp <- newForeignPtr a (free a)
>         return (StorableArray l u fp)
> 
> That's using the old type of newForeignPtr.  How can that be rewritten
> using the new type, without Alastair's ptr_free?  I guess one could use
> mallocForeignPtrBytes and duplicate the MarshalArray stuff, but that
> seems ugly.
> 
> So Alastair's proposal gets back some of what was lost in the change of
> newForeignPtr, though it's only a partial solution.  (It doesn't cover
> the use in Text.Regex.Posix, for example.)

Ok, I misunderstood you.  

In a sense, the change to newForeignPtr means that it really
can only be used for foreign resources.  Currently, the FFI's
malloc-functions provide a Haskell version of C's storage
model, but don't guarantee that the same storage manager is
used.  As a result, we cannot use Haskell malloc'ed
resources with foreign pointers.

We have four alternatives:

(1) We leave everything as it is.  If you want malloc-type
    storage that you can free in a finaliser, you need to
    write your own interface to C's malloc() and free().

(2) We commit to using C's storage manager in Haskell's
    malloc routines.  Then, C's free() can be used to free
    storage allocated with Haskell's malloc routines.
    (Whether we already provide a foreign import declaration
    to access &free from Haskell or leave that to the
    application is a minor detail.)

(3) We provide a value

      finalizerFree :: FunPtr (Ptr a -> IO ())

    that frees storage allocated with Haskell's malloc
    routines without any guarantee that this coincides with
    C's free().

(4) We add to the C land interface of the FFI a function

      void hs_free (void *);

    that behaves like MarshalAlloc.free, but can be called
    from a finalizer.  (One can import this with &hs_free.)

I don't like (2) much.  MarshalAlloc is part of the
language-independent marshalling support; so, it doesn't
seem right to bias the implementation towards C.

Whether (1) is a good option depends on how often people
would be forced to write their own interfaces.

(3) and (4) have essentially the same effect.  For matters
of convenience, we might actually consider doing both.
(Although, (4) suggests to also provide hs_malloc() and
hs_realloc().)  I can imagine that you might call a "real" C
routine in a finalizer that does some clean up and, then,
wants to deallocated storage, which would require hs_free().

Opinions?

Cheers,
Manuel



More information about the FFI mailing list