["Simon Marlow" <simonmar@microsoft.com>] RE: cvs commit: fptools/libraries/base/Foreign ForeignPtr.hs

Manuel M T Chakravarty chak at cse.unsw.edu.au
Wed Jan 22 02:18:21 EST 2003


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

> On Mon, Jan 20, 2003 at 11:03:36PM +1100, Manuel M T Chakravarty wrote:
> > Hence, I propose to leave the definition in the spec as it
> > was; ie, the equality of ForeignPtrs is defined via the
> > vanilla pointer that they encapsulate.
> 
> However, if you generalize ForeignPtrs (which I hope you will) this would
> require Eq on the underlying type.  I guess this is no great hardship
> for the types people want to use it with.

We actually would have two alternatives:

(1) We could define

      instance Eq a => Eq (ForeignObj a) where
        x == y = foreignObjToObj x == foreignObjToObj y

    and hence always reduce equality of ForeignObjs to the
    equality of the base type.  (Where this equality doesn't
    exist, we just don't have an equality on the
    corresponding ForeignObjs, but they are otherwise still
    usable.)

(2) We could have a builtin

      instance Eq (ForeignObj a)

    that implements equality by object identity and define
    ForeignPtr as follows:

      newtype ForeignPtr a = ForeignPtr (ForeignObj (Ptr a))

      instance Eq (ForeignPtr a) where
        (ForeignPtr x) == (ForeignPtr y) = 
	  foreignObjToObj x == foreignObjToObj y

    Alastair could, then, still get at his
    ForeignPtr-equality-as-identity definition whenever he
    wants.

I lean towards (2).  In fact, it is one more argument for
this generalisation of ForeignPtrs.  Hence, I propose that
we incorporate this generalisation unless there are any
serious objections.

Cheers,
Manuel



More information about the FFI mailing list