Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-07-03 Thread Manuel M T Chakravarty
Ross Paterson <[EMAIL PROTECTED]> wrote,

> On Thu, Jul 03, 2003 at 06:51:31PM +1000, Manuel M T Chakravarty wrote:
> > Ross Paterson <[EMAIL PROTECTED]> wrote,
> > 
> > > The new wording:
> > > 
> > >   \code{unsafePerformIO} may compromise typing; to avoid this, the programmer
> > >   should ensure that the result of \code{unsafePerformIO} has a monomorphic
> > >   type.
> > > 
> > > rules out the following:
> > > 
> > >   my_hash :: Storable a => a -> Int
> > >   my_hash a = fromIntegral $ unsafePerformIO $
> > >   allocaBytes (sizeof a) $ \p -> do
> > >   let size = fromIntegral (sizeOf a)
> > >   c_memset p 0 size
> > >   poke p a
> > >   hash_bytes p size
> > > 
> > >   foreign import ccall unsafe "memset"
> > >   c_memset :: Ptr a -> CInt -> CSize -> IO ()
> > >   foreign import ccall unsafe
> > >   hash_bytes :: Ptr a -> CSize -> IO CInt
> > 
> > Why is this ruled out?  hash_bytes returns a `CInt', which
> > is a monomorphic type.
> 
> The argument of unsafePerformIO has type forall a. Storable a => a -> CInt

Hmm, maybe we are talking about different things, but the
argument to `unsafePerformIO' must be of the form `IO a',
doesn't it.  Moreover, the above code applies `fromIntegral'
to the result of `unsafePerformIO'.  So, the result of
`unsafePerformIO' must be an integral type.

> > > Manuel writes:
> > > > However, it is possible to construct examples that are deterministic,
> > > > but still dubious from a typing perspective.  Let's assume a C routine
> > > > 
> > > >   void *foo();
> > > > 
> > > > that *always returns the same pointer* to a buffer area.  To
> > > > bind this in Haskell as
> > > > 
> > > >   foreign import ccall foo :: Ptr a
> > > > 
> > > > is problematic[1].
> > > 
> > > (a) It's constant across a run of the program, but its value still depends
> > > on the environment, and
> > 
> > Yes, and that's nothing that we want to rule out.  A
> > standard idiom for obtaining constant values from C is
> > 
> >   -= In C land =-
> > 
> >   int my_const ()
> >   {
> > ...
> > return ...;
> >   }
> > 
> >   -= In Haskell land =-
> > 
> >   const :: Int
> >   const = unsafePerformIO my_const
> > 
> >   foreign import ccall my_const :: IO Int
> > 
> > All that's required here is that my_const() is constant
> > within a program run.
> 
> Shouldn't it be constant in a global sense, e.g. getpid wouldn't be allowed?

No, I don't think so.  As long as it is constant for all
observations that the program can make, I don't see any
semantic problems.

Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-07-03 Thread Ross Paterson
On Thu, Jul 03, 2003 at 06:51:31PM +1000, Manuel M T Chakravarty wrote:
> Ross Paterson <[EMAIL PROTECTED]> wrote,
> 
> > The new wording:
> > 
> >   \code{unsafePerformIO} may compromise typing; to avoid this, the programmer
> >   should ensure that the result of \code{unsafePerformIO} has a monomorphic
> >   type.
> > 
> > rules out the following:
> > 
> > my_hash :: Storable a => a -> Int
> > my_hash a = fromIntegral $ unsafePerformIO $
> > allocaBytes (sizeof a) $ \p -> do
> > let size = fromIntegral (sizeOf a)
> > c_memset p 0 size
> > poke p a
> > hash_bytes p size
> > 
> > foreign import ccall unsafe "memset"
> > c_memset :: Ptr a -> CInt -> CSize -> IO ()
> > foreign import ccall unsafe
> > hash_bytes :: Ptr a -> CSize -> IO CInt
> 
> Why is this ruled out?  hash_bytes returns a `CInt', which
> is a monomorphic type.

The argument of unsafePerformIO has type forall a. Storable a => a -> CInt

> > Manuel writes:
> > > However, it is possible to construct examples that are deterministic,
> > > but still dubious from a typing perspective.  Let's assume a C routine
> > > 
> > >   void *foo();
> > > 
> > > that *always returns the same pointer* to a buffer area.  To
> > > bind this in Haskell as
> > > 
> > >   foreign import ccall foo :: Ptr a
> > > 
> > > is problematic[1].
> > 
> > (a) It's constant across a run of the program, but its value still depends
> > on the environment, and
> 
> Yes, and that's nothing that we want to rule out.  A
> standard idiom for obtaining constant values from C is
> 
>   -= In C land =-
> 
>   int my_const ()
>   {
> ...
> return ...;
>   }
> 
>   -= In Haskell land =-
> 
>   const :: Int
>   const = unsafePerformIO my_const
> 
>   foreign import ccall my_const :: IO Int
> 
> All that's required here is that my_const() is constant
> within a program run.

Shouldn't it be constant in a global sense, e.g. getpid wouldn't be allowed?
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-07-03 Thread Manuel M T Chakravarty
Ross Paterson <[EMAIL PROTECTED]> wrote,

> The new wording:
> 
>   \code{unsafePerformIO} may compromise typing; to avoid this, the programmer
>   should ensure that the result of \code{unsafePerformIO} has a monomorphic
>   type.
> 
> rules out the following:
> 
>   my_hash :: Storable a => a -> Int
>   my_hash a = fromIntegral $ unsafePerformIO $
>   allocaBytes (sizeof a) $ \p -> do
>   let size = fromIntegral (sizeOf a)
>   c_memset p 0 size
>   poke p a
>   hash_bytes p size
> 
>   foreign import ccall unsafe "memset"
>   c_memset :: Ptr a -> CInt -> CSize -> IO ()
>   foreign import ccall unsafe
>   hash_bytes :: Ptr a -> CSize -> IO CInt

Why is this ruled out?  hash_bytes returns a `CInt', which
is a monomorphic type.

> Manuel writes:
> > However, it is possible to construct examples that are deterministic,
> > but still dubious from a typing perspective.  Let's assume a C routine
> > 
> >   void *foo();
> > 
> > that *always returns the same pointer* to a buffer area.  To
> > bind this in Haskell as
> > 
> >   foreign import ccall foo :: Ptr a
> > 
> > is problematic[1].
> 
> (a) It's constant across a run of the program, but its value still depends
> on the environment, and

Yes, and that's nothing that we want to rule out.  A
standard idiom for obtaining constant values from C is

  -= In C land =-

  int my_const ()
  {
...
return ...;
  }

  -= In Haskell land =-

  const :: Int
  const = unsafePerformIO my_const

  foreign import ccall my_const :: IO Int

All that's required here is that my_const() is constant
within a program run.

Of course, I could have given a pure type in the foreign
import in this simple example, but that's not different from
an explicit `unsafePerformIO' and it is easy enough to
construct an example where this is not possible.

> (b) the declaration contains incorrect type information.

I guess, that's open to debate; ie, depends on how you
interpret C types in Haskell.

Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-24 Thread Ross Paterson
The new wording:

  \code{unsafePerformIO} may compromise typing; to avoid this, the programmer
  should ensure that the result of \code{unsafePerformIO} has a monomorphic
  type.

rules out the following:

my_hash :: Storable a => a -> Int
my_hash a = fromIntegral $ unsafePerformIO $
allocaBytes (sizeof a) $ \p -> do
let size = fromIntegral (sizeOf a)
c_memset p 0 size
poke p a
hash_bytes p size

foreign import ccall unsafe "memset"
c_memset :: Ptr a -> CInt -> CSize -> IO ()
foreign import ccall unsafe
hash_bytes :: Ptr a -> CSize -> IO CInt

I still claim that the problem isn't polymorphism itself, but creating
polymorphic references, and that is always environment dependent.

Manuel writes:
> However, it is possible to construct examples that are deterministic,
> but still dubious from a typing perspective.  Let's assume a C routine
> 
>   void *foo();
> 
> that *always returns the same pointer* to a buffer area.  To
> bind this in Haskell as
> 
>   foreign import ccall foo :: Ptr a
> 
> is problematic[1].

(a) It's constant across a run of the program, but its value still depends
on the environment, and
(b) the declaration contains incorrect type information.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-08 Thread Manuel M T Chakravarty
Malcolm Wallace <[EMAIL PROTECTED]> wrote,

> > > >   data Point
> > > >   foreign import getMousePos :: Ptr Point ->  IO ()
> > > >   foreign import getX :: Ptr Point -> IO Int
> > > >   foreign import getY :: Ptr Point -> IO Int
> 
> vs
> 
> >   data Point = Point (Ptr Point)
> >   foreign import getMousePos :: Point ->  IO ()
> 
> I like the second idiom.  You are right that there is no need for
> the application programmer to know whether pointers are involved,
> because even in the first style, it is not possible to 'peek' inside
> a Ptr Point to get the `actual' Point value.  So why not hide the
> pointer altogether?  Yes.

>From this, I infer that there is no dire need for empty data
types in conjunction with the FFI.  Consequently, I suggest
that we do not include empty data types into the FFI spec
(especially because the spec otherwise refrains from
extending the base language in any way other than by foreign
declarations).

Cheers,
Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-05 Thread Alastair Reid
ok, I'm convinced.  The semantics of empty datatypes can be a type inhabited 
only by bottom.

Hugs implements exactly that.

[Except in the special case of a few magical names (Int, Float, etc) when they 
occur in the Prelude (and only then).  Since it is only usable in the 
Prelude, they can be treated as an internal detail and ignored.]

--
Alastair
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-05 Thread Manuel M T Chakravarty
"Simon Marlow" <[EMAIL PROTECTED]> wrote,

>  
> > > > >   data Point
> > > > >   foreign import getMousePos :: Ptr Point ->  IO ()
> > > > >   foreign import getX :: Ptr Point -> IO Int
> > > > >   foreign import getY :: Ptr Point -> IO Int
> > 
> > vs
> > 
> > >   data Point = Point (Ptr Point)
> > >   foreign import getMousePos :: Point ->  IO ()
> > 
> > I like the second idiom.  You are right that there is no need for
> > the application programmer to know whether pointers are involved,
> > because even in the first style, it is not possible to 'peek' inside
> > a Ptr Point to get the `actual' Point value.  So why not hide the
> > pointer altogether?  Yes.
> 
> I presume that should be 'newtype' rather than 'data'?

True.

Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-05 Thread Simon Marlow
 
> > > >   data Point
> > > >   foreign import getMousePos :: Ptr Point ->  IO ()
> > > >   foreign import getX :: Ptr Point -> IO Int
> > > >   foreign import getY :: Ptr Point -> IO Int
> 
> vs
> 
> >   data Point = Point (Ptr Point)
> >   foreign import getMousePos :: Point ->  IO ()
> 
> I like the second idiom.  You are right that there is no need for
> the application programmer to know whether pointers are involved,
> because even in the first style, it is not possible to 'peek' inside
> a Ptr Point to get the `actual' Point value.  So why not hide the
> pointer altogether?  Yes.

I presume that should be 'newtype' rather than 'data'?

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-05 Thread Malcolm Wallace
> > Let's be clear about the role of Point here:  it is a dummy type
> > argument to Ptr, used to disambiguate the type 'Ptr Point' from any
> > other kind of Ptr.  It is for type-safety in the Haskell code.
> > 
> > It doesn't matter how many values of the type Point there are.  I could
> > use any Haskell type with the same results.
> >
> > There definitely aren't any values of type Point, so I don't see why it
> > needs a semantics.

OK, I think I agree with all of this.

> My main problem with this extension is the following:
> 
> * As we have learnt, nhc98 and Hugs use `data T' for an
>   entirely different purpose than the one proposed by John
>   (namely to represent primitive external types).  It may be
>   possible to abuse nhc98 and Hugs `data T' also in the way
>   John wants it (and GHC provides it), but this sounds less
>   straight forward than initially where the impression was
>   given that the three systems already implement the same
>   extension.

Actually, I think both Hugs and nhc98 straightforwardly allow
John's use.  All three systems do implement the same extension.

In fact it is the current usage of 'data T' for primitive types that
is tricky.  At the moment, basically they must be *internal* types,
i.e. types already known to the Haskell runtime system.  The idea
of using them for external, previously unknown, types is entirely
speculative.  It would require somehow specifying storage sizes, and
routines to marshal values into the heap, and perhaps more.  None of
these mechanisms yet exist.  The question was raised as to whether we
might one day want those facilities, because the natural place to
specify them is in the FFI.  But no-one even has a proposal for how
it might work, so I think we can safely dismiss it at this stage.

> > >   data Point
> > >   foreign import getMousePos :: Ptr Point ->  IO ()
> > >   foreign import getX :: Ptr Point -> IO Int
> > >   foreign import getY :: Ptr Point -> IO Int

vs

>   data Point = Point (Ptr Point)
>   foreign import getMousePos :: Point ->  IO ()

I like the second idiom.  You are right that there is no need for
the application programmer to know whether pointers are involved,
because even in the first style, it is not possible to 'peek' inside
a Ptr Point to get the `actual' Point value.  So why not hide the
pointer altogether?  Yes.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-05 Thread Manuel M T Chakravarty
"Simon Marlow" <[EMAIL PROTECTED]> wrote,

> > We routinely use code like this:
> > 
> >   data Point
> >   foreign import getMousePos :: Ptr Point ->  IO ()
> >   foreign import getX :: Ptr Point -> IO Int
> >   foreign import getY :: Ptr Point -> IO Int
> > 
> > The idea being that:
> > 
> > 1) there is a foreign type (which might be called Point, 
> > MousePos, point_t, struct point or whatever)
> > 
> > 2) that we have a pointer to it
> > 
> > 3) that the thing we have a pointer to can take on a number 
> > of different 
> > values.  We don't know what the values are but this doesn't 
> > mean they don't exist.
> 
> Let's be clear about the role of Point here:  it is a dummy type
> argument to Ptr, used to disambiguate the type 'Ptr Point' from any
> other kind of Ptr.  It is for type-safety in the Haskell code.
> 
> Additionally, the type argument to Ptr is used to resolve overloading
> when doing marshalling using the Storable class, but we're not using
> that facility here because no marshalling is going on.
> 
> There definitely aren't any values of type Point, so I don't see why it
> needs a semantics.  The semantics of empty data declarations seems like
> an entirely orthogonal issue, and I don't see any problem with the
> current semantics for empty data declarations, which is a completely
> natural degenerate case of ordinary data declarations.
> 
> > > And what do you mean by a trick?
> > 
> > It is possible that, since we cannot directly observe values 
> > of foreign types, 
> > we can safely model the type as having just one value 
> > (bottom) or, perhaps 
> > even no values at all.  By this I mean that exactly the same 
> > properties can 
> > be proved whether we use an accurate model or a simplified model.
> > 
> > But, it is a trick because we know that there is not just one 
> > (or zero) values in that type (at least, for most types).
> 
> I don't agree with that last sentence: there's no trickery going on; it
> doesn't matter how many values of the type Point there are.  I could use
> any Haskell type with the same results.
> 
> Let me say this another way:  the type argument to Ptr in no way
> represents the type of the foreign data.  It is used to resolve
> overloading and to disciminate pointer types in Haskell marshalling
> code, that's all.  There is no link between the semantics of the Haskell
> type and the semantics of the foreign type (whatever that might be), and
> we shouldn't confuse the issue by pretending that there is.

Exactly what I think, too.  Empty data types are used as
Skolem constants in the type checker.

Alastair wrote earlier that `data T' is not inhibited
(except by bottom as we have a lazy language).  That's
semantically exactly what we want.  Hence, if the compiler
wants to regard two values of type `T' to be the same, it is
perfectly reasonable to do that.  That's the point where
IMHO Alastair's earlier argument was flawed (and what has
led to the misunderstanding).

My main problem with this extension is the following:

* As we have learnt, nhc98 and Hugs use `data T' for an
  entirely different purpose than the one proposed by John
  (namely to represent primitive external types).  It may be
  possible to abuse nhc98 and Hugs `data T' also in the way
  John wants it (and GHC provides it), but this sounds less
  straight forward than initially where the impression was
  given that the three systems already implement the same
  extension.

* So far, the FFI addendum has managed to stay away from
  changing anything at H98's syntax other than adding
  `foreign'.  I am reluctant to change that, but then it is
  really a very small change that won't break anything.

BTW, I tend to use the following (which - suprise, suprise -
is what c2hs generates in that situation):

  data Point = Point (Ptr Point)

  foreign import getMousePos :: Point ->  IO ()

No need for an extension here and I hide from the
application programmer the fact that the argument to
`getMousePos' is a pointer.

Cheers,
Manuel

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-04 Thread Malcolm Wallace
> > > > * 6.2:   All the types in CTypes must be newtypes that are exported
> > > >  abstractly. 
> > 
> > How about exporting them non-abstractly for nhc98 only, and adding a
> > comment to explain why the workaround is necessary?
> 
> That's what I prefer, too.

OK, that's what I've done.  The spec can stand as it is.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-04 Thread Manuel M T Chakravarty
"Simon Marlow" <[EMAIL PROTECTED]> wrote,

> > Manuel M T Chakravarty <[EMAIL PROTECTED]> writes:
> > 
> > > -=- Changes since RC 9
> > > 
> > > * 6.2:   All the types in CTypes must be newtypes that are exported
> > >  abstractly. 
> > 
> > This change makes things highly inconvenient in nhc98.  A newtype
> > can only be passed across the FFI in nhc98 if we have enough
> > information to determine the original type that is being renamed.
> > If Foreign.C.Types exports them abstractly, then currently we do not
> > have that information, and so these types cannot be used at all!
> > 
> > I am not suggesting that the newtype constructors should necessarily
> > be part of the API seen by the user, but the problem comes down to a
> > known deficiency in nhc98's interface file conventions.  
> 
> How about exporting them non-abstractly for nhc98 only, and adding a
> comment to explain why the workaround is necessary?

That's what I prefer, too.

Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-04 Thread Manuel M T Chakravarty
Ross Paterson <[EMAIL PROTECTED]> wrote,

> Minor nits: there's a footnote saying "Finalizers in Haskell cannot
> be savely [sic] realised without requiring support for pre-emptive
> concurrency".  I'd suggest dropping "pre-emptive": with cooperative
> concurrency it's perfectly safe to collect the finalizers in GC and fork
> them next time you're back in the IO monad (though it's not very timely).

True.  Thanks,
Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Simon Marlow
> We routinely use code like this:
> 
>   data Point
>   foreign import getMousePos :: Ptr Point ->  IO ()
>   foreign import getX :: Ptr Point -> IO Int
>   foreign import getY :: Ptr Point -> IO Int
> 
> The idea being that:
> 
> 1) there is a foreign type (which might be called Point, 
> MousePos, point_t, struct point or whatever)
> 
> 2) that we have a pointer to it
> 
> 3) that the thing we have a pointer to can take on a number 
> of different 
> values.  We don't know what the values are but this doesn't 
> mean they don't exist.

Let's be clear about the role of Point here:  it is a dummy type
argument to Ptr, used to disambiguate the type 'Ptr Point' from any
other kind of Ptr.  It is for type-safety in the Haskell code.

Additionally, the type argument to Ptr is used to resolve overloading
when doing marshalling using the Storable class, but we're not using
that facility here because no marshalling is going on.

There definitely aren't any values of type Point, so I don't see why it
needs a semantics.  The semantics of empty data declarations seems like
an entirely orthogonal issue, and I don't see any problem with the
current semantics for empty data declarations, which is a completely
natural degenerate case of ordinary data declarations.

> > And what do you mean by a trick?
> 
> It is possible that, since we cannot directly observe values 
> of foreign types, 
> we can safely model the type as having just one value 
> (bottom) or, perhaps 
> even no values at all.  By this I mean that exactly the same 
> properties can 
> be proved whether we use an accurate model or a simplified model.
> 
> But, it is a trick because we know that there is not just one 
> (or zero) values in that type (at least, for most types).

I don't agree with that last sentence: there's no trickery going on; it
doesn't matter how many values of the type Point there are.  I could use
any Haskell type with the same results.

Let me say this another way:  the type argument to Ptr in no way
represents the type of the foreign data.  It is used to resolve
overloading and to disciminate pointer types in Haskell marshalling
code, that's all.  There is no link between the semantics of the Haskell
type and the semantics of the foreign type (whatever that might be), and
we shouldn't confuse the issue by pretending that there is.

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Alastair Reid
On Tuesday 03 June 2003 10:15 am, Simon Marlow wrote:

> > We know that T must contain bottom.
>
> Not necessarily - GHC's primitive types don't contain bottom.

Of course, GHC's primitive types aren't in the standard.

> But I'm probably just being awkward, since I really don't understand
> what it is you're trying to do here.

I'm trying to give a semantics to the existing feature of using empty data 
declarations with the ffi.

Second to that, I am checking that the existing syntax matches the semantics.

I definitely do not want to add the ability to marshal these types because we 
already have a fine way of dealing with them (i.e., a wide range of 
explicitly sized types plus hsc2hs/autoconf).
  
> I'd be happy for semantics to reflect reality - but what *is* the
> reality that you're trying to model?

We routinely use code like this:

  data Point
  foreign import getMousePos :: Ptr Point ->  IO ()
  foreign import getX :: Ptr Point -> IO Int
  foreign import getY :: Ptr Point -> IO Int

The idea being that:

1) there is a foreign type (which might be called Point, MousePos, point_t, 
struct point or whatever)

2) that we have a pointer to it

3) that the thing we have a pointer to can take on a number of different 
values.  We don't know what the values are but this doesn't mean they don't 
exist.

> And what do you mean by a trick?

It is possible that, since we cannot directly observe values of foreign types, 
we can safely model the type as having just one value (bottom) or, perhaps 
even no values at all.  By this I mean that exactly the same properties can 
be proved whether we use an accurate model or a simplified model.

But, it is a trick because we know that there is not just one (or zero) values 
in that type (at least, for most types).

> As far as I can tell, you want a type T that represents a foreign
> object.  What is the representation of this foreign object?  How is it
> marshalled to and from the foreign language?

We already have types which represent foreign types.
We can give this existing feature a semantics without having to define its 
representation or add marshalling.

> I think an example would really help.  Invent some syntax and extra
> features if you need to!

The Point example above is what I want (i.e., what we already have).

I'm tempted to change the syntax to something like:

  foreign import type Point

to make it a little more obvious when you find it in source code but apart 
from that I'm not contemplating any change in implementations.

--
Alastair Reid
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Simon Marlow
 
> On Monday 02 June 2003 2:32 pm, Simon Marlow wrote:
> 
> > Ok.  But I still don't understand why the whole discussion 
> isn't moot.
> > I can't see how to acquire a value of type T that isn't bottom.  
> 
> Whether you can acquire values of this type or not, we need 
> to give it a semantics.
>
> We know that T must contain bottom.

Not necessarily - GHC's primitive types don't contain bottom.

But I'm probably just being awkward, since I really don't understand
what it is you're trying to do here.

> > Could you give an example?
> 
> No , I probably can't come up with an example as things stand 
> at the moment.  
> But who knows what changes we might make in the future and 
> when we do, we're 
> bound to do better if our semantics relfects reality instead 
> of relying on a trick.

I'd be happy for semantics to reflect reality - but what *is* the
reality that you're trying to model?  And what do you mean by a trick?

As far as I can tell, you want a type T that represents a foreign
object.  What is the representation of this foreign object?  How is it
marshalled to and from the foreign language?

I think an example would really help.  Invent some syntax and extra
features if you need to!

Cheers,
Simon

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Simon Marlow
Alastair Reid writes:

> I strongly agree that we should definitely add the ability to 
> declare types 
> whose definition is provided externally.  (i.e., provide the 
> feature that empty datatype decls currently provide.)
> 
> Before adding them, we need to agree on the semantics and 
> syntax (in that order I think).
> 
> The obvious semantics based on the syntax is:
> 
> [[
>   The declaration
> 
> data T
> 
>   introduces a type T whose only value is bottom.
> ]]
> 
> This semantics is obviously flawed though because it would 
> suggest that any 
> two values of type T are equal (and equal to bottom) and that 
> optimizations 
> based on that equality are valid.  Using an unpointed type 
> (i.e., the value 
> is not bottom) or saying there are no values bottom or 
> otherwise don't help.
> 
> The correct semantics has to be something roughly like:
> 
> [[
>   The declaration
> 
> data T
> 
>   declares a type T whose set of values are defined externally to the
>   language. [optional sentence: There are no legal Haskell operations 
>   on values of type T.]
> ]]

If we were actually using values of type T in the way you suggest, I would agree.  But 
the way these empty datatypes are being used
is as dummy type arguments to Ptr, as in 'Ptr T'.  So I don't think there's any need 
to give special semantics to datatypes declared
with empty declarations.

(this is essentially what Marcin just said, but I'm being a bit more verbose).

Cheers,
Simon

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Fergus Henderson
On 02-Jun-2003, Alastair Reid <[EMAIL PROTECTED]> wrote:
> 
> > The Mercury compiler will generate appropriate glue code to marshal and
> > unmarshal values of that type.
> 
> How does it figure out what concrete type to use?  Does it use trial 
> compilations a la autoconf?

No.  We don't try to second-guess the C compiler.  We just let the C
compiler figure it out.  The Mercury compiler generates a small amount
of glue code in C, and invokes the C compiler on that code.

The glue code consists of a wrapper around every foreign function
(although if you wanted to optimize things, you might note that this is
only really needed for foreign functions whose arguments or result are
foreign types).  The glue code interface uses only known types such as
WORD, so it can be called in a straight-forward manner from the assembly
code that the Mercury compiler's assembly-language back-end generates.
The glue code for each function calls the function, boxing or unboxing
the arguments and/or results if needed, i.e. if they have a foreign type
which doesn't fit in a word.

This approach of boxing all foreign types has the major advantage that
these foreign types can be passed to polymorphically typed Mercury
procedures or inserted in polymorphically typed Mercury data structures.

Generating a wrapper for every foreign function also means that it is
possible to interface to C macros as well as to C functions.
In fact, we also allow interfacing with arbitrary C code fragments,
not just macros or functions, so you can use this feature to write
inline asm, for example.

To illustate how the wrappers work, here's what the glue code for a
function "foo :: T -> T", where "T" is a foreign type implemented by
the C type "CT", could look like:

WORD foo_glue(WORD boxed_x) {
WORD boxed_y;
CT x, y;

/* maybe unbox the function's input argument */
x = *(CT *)(sizeof(CT) > sizeof(WORD) ? boxed_x : &boxed_x);

/* call the function or macro foo() */
y = foo(x);

/* maybe box the function's result */
if (sizeof(CT) > sizeof(WORD)) {
boxed_y = (WORD) GC_malloc(sizeof(CT));
*(CT *)boxed_y = y;
} else {
*(CT *)&boxed_y = y;
}

return boxed_y;
}

Note that if compiling to C, such wrappers can be inlined.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Alastair Reid
On Monday 02 June 2003 2:32 pm, Simon Marlow wrote:

> Ok.  But I still don't understand why the whole discussion isn't moot.
> I can't see how to acquire a value of type T that isn't bottom.  

Whether you can acquire values of this type or not, we need to give it a 
semantics.

We know that T must contain bottom.

I'd argue that even if we can't manipulate or observe them, the
 semantics should admit that the type contains a bunch of other
 (foreign) values because it is more accurate and having an
 accurate semantics is bound to pay off.

> Could you give an example?

No , I probably can't come up with an example as things stand at the moment.  
But who knows what changes we might make in the future and when we do, we're 
bound to do better if our semantics relfects reality instead of relying on a 
trick.

--
Alastair

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Alastair Reid

> Using `newtype T = MkT Int8' or equivalent only works for foreign data
> types whose representation is known.  How do you deal with C's "time_t",
> for example?  Or with C "struct" types?  The user doesn't want to make
> non-portable assumptions about what padding the C compiler is going
> to insert.

The usual way is to use some autoconf magic or the hsc2hs preprocessor to 
figure it out.  The key part of fptools/aclocal.m4:FPTOOLS_CHECK_HTYPE
is this program:

typedef $1 testing;

main() {
  FILE *f=fopen("conftestval", "w");
  if (!f) exit(1);
  if (((testing)((int)((testing)1.4))) == ((testing)1.4)) {
fprintf(f, "%s%d\n",
   ((testing)(-1) < (testing)0) ? "Int" : "Word",
   sizeof(testing)*8);
  } else {
fprintf(f,"%s\n",
   (sizeof(testing) >  sizeof(double)) ? "LDouble" :
   (sizeof(testing) == sizeof(double)) ? "Double"  : "Float");
  }
  fclose(f);
  exit(0);
}


> But to deal with cases like the ones mentioned above,
> Mercury also allows the user to declare how such types are
> represented in foreign languages, using `pragma foreign_type'
>
> declarations:
>   :- pragma foreign_type("C", t, "some_c_typename").
>
> The Mercury compiler will generate appropriate glue code to marshal and
> unmarshal values of that type.

How does it figure out what concrete type to use?  Does it use trial 
compilations a la autoconf?


> In fact, the "data Int" declaration need not even be physically
> present; the implementation could just insert it in the Prelude
> automatically. (That's what the Mercury implementation does for its builtin
> types.)

Hugs used to insert it automatically but we found that putting the 
declarations in the Prelude source code:

1) Made the source closer to the report and made the Prelude
a little easier to understand.
2) Reduced the amount of magic required in the compiler.

--
Alastair

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> writes:

> Are you suggesting we ought to be able to define new primitive types?

Sorry, yes indeed that was the suggestion.

Or at least, it is not so much a suggestion, as a recognition that
Hugs and nhc98 already use the 'data T' mechanism for this purpose,
so we should consider if there might be possible confusion when
adding a mechanism to the FFI standard which has the same syntax but
a different purpose.

One design alternative would be to extend the FFI standard to allow
the addition of new primitive types.

Another design alternative would be to use different names for
the primitive datatype mechanism and the empty datatype mechanism.
(Way back when, nhc13 had "data primitive Int" for the former instead
of "data Int", and Alastair has just suggested "foreign import data T"
as a possible syntax for the latter.)

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Simon Marlow
 
> Using `newtype T = MkT Int8' or equivalent only works for foreign data
> types whose representation is known.  How do you deal with 
> C's "time_t",
> for example?  Or with C "struct" types?  The user doesn't want to make
> non-portable assumptions about what padding the C compiler is going
> to insert.
> 
> Like Haskell, Mercury allows data definitions with no body:
> 
>   :- type t.
> 
> But to deal with cases like the ones mentioned above,
> Mercury also allows the user to declare how such types are
> represented in foreign languages, using `pragma foreign_type'
> declarations:
> 
>   :- pragma foreign_type("C", t, "some_c_typename").
> 
> The Mercury compiler will generate appropriate glue code to 
> marshal and unmarshal values of that type.

We have similar support in some of the Haskell FFI Tools.  For example,
using hsc2hs I can write:

newtype CTime = CTime $(type time_t)

and this will be converted into

newtype CTime = CTime (Int32)

(or whatever) when hsc2hs processes the source.  Ok, it's
language-dependent, but it has the advantage that it doesn't require any
extra support from the compiler, and nothing needs to be added to the
FFI spec.

Similar mechanisms can be (and are) used for marshalling C structs
without baking in the field offsets and types.

Cheers,
Simon

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Fergus Henderson
On 02-Jun-2003, Simon Marlow <[EMAIL PROTECTED]> wrote:
>  
> > On 02-Jun-2003, Simon Marlow <[EMAIL PROTECTED]> wrote:
> > >  
> > > I can't see how to acquire a value of type T that isn't bottom.
> > 
> > By calling a function defined using the FFI, of course.
> 
> But the FFI lists the types that may be returned by a foreign function,
> and T is not one of them.

Ah, I see.

> Are you suggesting we ought to be able to define new primitive types?

I think it is at least worth considering.  See my other message about
how Mercury deals with this issue.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-03 Thread Fergus Henderson
On 02-Jun-2003, Alastair Reid <[EMAIL PROTECTED]> wrote:
> If all the compiler is given is:
> 
>   data T
> 
> where T is not a builtin type, the compiler can't possible know how to 
> represent or marshall it.  (And since we can already do that using 'newtype T 
> = MkT Int8' I don't think we need to add another mechanism.)

Using `newtype T = MkT Int8' or equivalent only works for foreign data
types whose representation is known.  How do you deal with C's "time_t",
for example?  Or with C "struct" types?  The user doesn't want to make
non-portable assumptions about what padding the C compiler is going
to insert.

Like Haskell, Mercury allows data definitions with no body:

:- type t.

But to deal with cases like the ones mentioned above,
Mercury also allows the user to declare how such types are
represented in foreign languages, using `pragma foreign_type'
declarations:

:- pragma foreign_type("C", t, "some_c_typename").

The Mercury compiler will generate appropriate glue code to marshal and
unmarshal values of that type.

You might want to consider something like this for Haskell.
(Either that, or resign yourselves to this aspect of Haskell's FFI
being less expressive than Mercury! ;-)

In Mercury, you can even give a simple type different foreign_type
declarations for different languages:

:- type time.
:- pragma foreign_type("C", time, "time_t").
:- pragma foreign_type("il", time, "[mscorlib]System.DateTime").
:- pragma foreign_type("java", time, "Java.util.Date").

The Mercury compiler will choose whichever language is most appropriate
given the compilation options (e.g. when compiling to C or assembler,
it will use the "C" version, when compiling to .NET it will use the "il"
version, and when compiling to Java it will use the Java version).

> Although it is similar, I think
> 
>   data Int
> 
> with a builtin type is a different thing from what we're doing when we write:
> 
>   data T
> 
> for some foreign type.

Sure.  In fact, the "data Int" declaration need not even be physically
present; the implementation could just insert it in the Prelude automatically.
(That's what the Mercury implementation does for its builtin types.)

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Simon Marlow
 
> On 02-Jun-2003, Simon Marlow <[EMAIL PROTECTED]> wrote:
> >  
> > I can't see how to acquire a value of type T that isn't bottom.
> 
> By calling a function defined using the FFI, of course.

But the FFI lists the types that may be returned by a foreign function,
and T is not one of them.

Are you suggesting we ought to be able to define new primitive types?

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Fergus Henderson
On 02-Jun-2003, Simon Marlow <[EMAIL PROTECTED]> wrote:
>  
> I can't see how to acquire a value of type T that isn't bottom.

By calling a function defined using the FFI, of course.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Fergus Henderson
On 02-Jun-2003, Alastair Reid <[EMAIL PROTECTED]> wrote:
> 
> I was just trying to show how to create a value of type
> T which might be bottom.  It would have been easier to use:
> 
>   t :: T
>   t = undefined

The same issue arises for ghc's unboxed types, of course.
ghc has some complicated extension to the type system to deal with it,
which makes examples like the one above type errors if T is an unboxed type.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Simon Marlow
 
> > I'm not following this. what exactly is derefPtr?  The only 
> analogous
> > function I can think of is Foreign.peek:
> 
> Sorry, I meant peek.
> 
> > but peek will unmarshal the value at the end of the Ptr into T, so T
> > cannot be abstract.
> 
> Sorry, I was just trying to show how to create a value of type
> T which might be bottom.  It would have been easier to use:
> 
>   t :: T
>   t = undefined

Ok.  But I still don't understand why the whole discussion isn't moot.
I can't see how to acquire a value of type T that isn't bottom.  Could
you give an example?

Cheers,
Simon

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Alastair Reid

> I'm not following this. what exactly is derefPtr?  The only analogous
> function I can think of is Foreign.peek:

Sorry, I meant peek.

> but peek will unmarshal the value at the end of the Ptr into T, so T
> cannot be abstract.

Sorry, I was just trying to show how to create a value of type
T which might be bottom.  It would have been easier to use:

  t :: T
  t = undefined

--
Alastair
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Simon Marlow
 
> I don't think we have much choice about whether undefined 
> values are part of 
> the type.  If you can create a value of that type:
> 
>   x <- derefPtr (px :: Ptr T)

I'm not following this. what exactly is derefPtr?  The only analogous
function I can think of is Foreign.peek:

  peek :: Storable a => Ptr a -> IO a

but peek will unmarshal the value at the end of the Ptr into T, so T
cannot be abstract.

Cheers,
Simon

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Alastair Reid
On Monday 02 June 2003 11:14 am, Malcolm Wallace wrote:
> How about something like:
>
>   The declaration
>   data T
>   declares an abstract datatype T, whose values and operations are
>   defined external to the Haskell language.  Values of T follow
>   the semantics of the foreign language, in particular, with respect
>   to mutability and the admission of the undefined value.

I don't think we have much choice about whether undefined values are part of 
the type.  If you can create a value of that type:

  x <- derefPtr (px :: Ptr T)

then you can create a thunk of that type:

  let y = if  then x else y

and that thunk can be bottom.

> This raises the question of whether it should be possible to declare
> foreign functions directly over such types, [...]  However,
> I know that nhc98 internally at least uses the former style in order
> to implement built-in types like arrays, big integers, etc.

Hugs implements its builtin types this way too (and did so long before the ffi 
came along).  It works because Hugs magically knows how toi implement Int, 
Float, etc. - it knows about any typechecking rules and, most importantly, it 
knows how to represent and marshall values of builtin types.  If all the 
compiler is given is:

  data T

where T is not a builtin type, the compiler can't possible know how to 
represent or marshall it.  (And since we can already do that using 'newtype T 
= MkT Int8' I don't think we need to add another mechanism.)

Although it is similar, I think

  data Int

with a builtin type is a different thing from what we're doing when we write:

  data T

for some foreign type.

--
Alastair Reid
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Malcolm Wallace
John Meacham wrote:

> > This was discussed here before and there seemed to be some support for
> > it, but how about adding the empty data declaration extension to the FFI
> > spec?

I agree, it would be a suitable addition to the FFI, since it is the
place where such types make most sense.


Alastair Reid <[EMAIL PROTECTED]> writes:

> The correct semantics has to be something roughly like:
> 
> [[
>   The declaration
> 
> data T
> 
>   declares a type T whose set of values are defined externally to the
>   language. [optional sentence: There are no legal Haskell operations 
>   on values of type T.]
> ]]

I don't really like the optional sentence, since it suggests that
a foreign imported function that operates over such values is not
legal Haskell.  How about something like:

  The declaration
  data T
  declares an abstract datatype T, whose values and operations are
  defined external to the Haskell language.  Values of T follow
  the semantics of the foreign language, in particular, with respect
  to mutability and the admission of the undefined value.

This raises the question of whether it should be possible to declare
foreign functions directly over such types, rather than through
pointers, e.g.

data T
foreign import mkT  :: IO T
foreign import fooT :: T -> T

rather than

data T
foreign import mkT  :: IO (Ptr T)
foreign import fooT :: Ptr T -> Ptr T

Obviously the former is much less safe than the latter.  However,
I know that nhc98 internally at least uses the former style in order
to implement built-in types like arrays, big integers, etc.  I'm not
suggesting we should necessarily formalise that hack as part of the
FFI standard - I'm just raising the question for consideration (and
probable rejection), so that our choice is an informed one.

> I'm not especially keen to change the syntax (especially since the existing 
> syntax is so trivial to implement) but if we're going to add this to the
> language, we should make sure the syntax and semantics are tolerably
> clear and in agreement with each other.

I'm not keen to change the syntax either.  The current style is pretty
clear to my mind.  But it is right that we should think about it.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Marcin 'Qrczak' Kowalczyk
Dnia nie 1. czerwca 2003 23:55, Alastair Reid napisaƂ:

>   introduces a type T whose only value is bottom.
> ]]
>
> This semantics is obviously flawed though because it would suggest that any
> two values of type T are equal (and equal to bottom) and that optimizations
> based on that equality are valid.

Since no values of type T are ever created or manipulated, what difference 
does it make?

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Alastair Reid
On Saturday 31 May 2003 10:11 pm, John Meacham wrote:
> This was discussed here before and there seemed to be some support for
> it, but how about adding the empty data declaration extension to the FFI
> spec?

I strongly agree that we should definitely add the ability to declare types 
whose definition is provided externally.  (i.e., provide the feature that 
empty datatype decls currently provide.)

Before adding them, we need to agree on the semantics and syntax (in that 
order I think).

The obvious semantics based on the syntax is:

[[
  The declaration

data T

  introduces a type T whose only value is bottom.
]]

This semantics is obviously flawed though because it would suggest that any 
two values of type T are equal (and equal to bottom) and that optimizations 
based on that equality are valid.  Using an unpointed type (i.e., the value 
is not bottom) or saying there are no values bottom or otherwise don't help.

The correct semantics has to be something roughly like:

[[
  The declaration

data T

  declares a type T whose set of values are defined externally to the
  language. [optional sentence: There are no legal Haskell operations 
  on values of type T.]
]]

If we go with a semantics like that, different syntax suggests itself like:

  external data T

or, better, 

  foreign import data T

I'm not especially keen to change the syntax (especially since the existing 
syntax is so trivial to implement) but if we're going to add this to the
language, we should make sure the syntax and semantics are tolerably
clear and in agreement with each other.

--
Alastair Reid
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-01 Thread John Meacham
This was discussed here before and there seemed to be some support for
it, but how about adding the empty data declaration extension to the FFI
spec? They are used quite often to represent the abstract targets of
pointers as in:

data Foo
data Bar

foreign  lookupBar :: Ptr Foo -> IO (Ptr Bar)  -- psuedocode

the FFI is the perfect place to use the extension and it is trivial to
implement. The problem is made even worse by the fact that you can't use
the beginning underscore trick with data constructors since an
underscore counts as a lowercase letter so there is no way to avoid
unused constructor warning messages without resorting to using
extensions or resorting to compiler-specific pragmas which are
unelegant.

so I guess my argument is in a nutshell, everyone implements them. they
are a very good fit with the FFI and they make code more readable and
supress spurious warnings.
John


-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-05-28 Thread Simon Marlow
 
> Manuel M T Chakravarty <[EMAIL PROTECTED]> writes:
> 
> > -=- Changes since RC 9
> > 
> > * 6.2:   All the types in CTypes must be newtypes that are exported
> >  abstractly. 
> 
> This change makes things highly inconvenient in nhc98.  A newtype
> can only be passed across the FFI in nhc98 if we have enough
> information to determine the original type that is being renamed.
> If Foreign.C.Types exports them abstractly, then currently we do not
> have that information, and so these types cannot be used at all!
> 
> I am not suggesting that the newtype constructors should necessarily
> be part of the API seen by the user, but the problem comes down to a
> known deficiency in nhc98's interface file conventions.  

How about exporting them non-abstractly for nhc98 only, and adding a
comment to explain why the workaround is necessary?

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-05-27 Thread Malcolm Wallace
Manuel M T Chakravarty <[EMAIL PROTECTED]> writes:

> -=- Changes since RC 9
> 
> * 6.2:   All the types in CTypes must be newtypes that are exported
>  abstractly. 

This change makes things highly inconvenient in nhc98.  A newtype
can only be passed across the FFI in nhc98 if we have enough
information to determine the original type that is being renamed.
If Foreign.C.Types exports them abstractly, then currently we do not
have that information, and so these types cannot be used at all!

I am not suggesting that the newtype constructors should necessarily
be part of the API seen by the user, but the problem comes down to a
known deficiency in nhc98's interface file conventions.  

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi