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 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 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
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-05 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-05 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-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-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 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-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 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
 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-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-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 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 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 expression 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 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

 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-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