HTML version of the H98 FFI Addendum

2005-04-23 Thread Manuel M T Chakravarty
Finally!  The Haskell 98 addendum for the Foreign Function Interface 1.0
in HTML format.  Browse online or download at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

I apologise for the slowness in producing this format.

Manuel

PS: XHTML 1.0 with CSS 2.1 produced by tex4ht 
http://www.cse.ohio-state.edu/~gurari/TeX4ht/

PPS: Shouldn't this be hosted at haskell.org?


___
FFI mailing list
FFI@haskell.org
http://www.haskell.org/mailman/listinfo/ffi


Re: Request: withArrayLength

2004-03-22 Thread Manuel M T Chakravarty
On Tue, 2004-03-23 at 05:55, Sven Panne wrote:
 Once upon a time, I wrote:
  Adrian Hey wrote:
  
  [...] I think..
 
   withArrayLength :: Storable a = [a] - (Ptr a - Int - IO b) - IO b
 
  would be useful because you often need the length in a foreign function
  
  I would support that, similar situations happened a few times in my
  OpenGL/GLUT stuff.
  
  and I guess withArray must pre-calculate the length before allocating
  storage in any case [...]
  
  Yep.
 
 There has been no other response yet, so I'd like to raise this issue again.
 If we decide to add this to the module, it should be documented in the FFI
 addendum as well, BTW. Any opionions?

I think we need to decide how the further development of the FFI will
proceed.  Given that Version 1.0 of the Addendum is frozen, I am not in
favour of changing the Addendum anytime soon and certainly not for small
matters, such as a convenience function.

We might want to accumulate extra useful functions in the implementation
in an *extra* module and once there is enough interesting functionality
in there, we can start talking about Version 1.1 of the Addendum.

Does this sound like a sensible approach?

Manuel


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


ANN: H98 FFI Addendum 1.0, Release Candidate 16

2003-11-17 Thread Manuel M T Chakravarty
Dear Haskell Folks,

Release Candidate 16 of the H98 FFI Addendum 1.0 is now
available from

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

Since the last version of the Addendum announced on
[EMAIL PROTECTED], namely RC12, the FFI Task Force
decided on a slight generalisation of the interface to
finalizers as well as the addition of some support for
string marshalling for characters sets beyond ASCII.  A
detailed change log is at the end of this message.

I'd like to propose RC16 as the final form of Version 1.0 of
the FFI Addendum.  If you find any problems with this
version, please raise them within the next two weeks.

Cheers,
Manuel

-=-

Changes since RC15:
* 6.3: Footnote regarding __STDC_ISO_10646__ added to text introducing
   `CWString'.

Changes since RC14:
* 6.2: CWChar - CWchar
* 6.3: - CWChar - CWchar
   - Stated explicitly that memory allocated by `newCString' and friends
 can be deallocated by `MarshalAlloc.free'
   - Improved documentation

Changes since RC13:
* 5.3: Fixed typo
* 5.7: Fixed a mistake in the type of `peekByteOff' and `pokeByteOff' (the
   type variable constrained by `Storable' must be different from the
   parameter of the `Ptr')
* 6.3: Improved documentation

Changes since RC12:
* Acks : Added John Meacham
* 4.1.5: Bug fix courtesy of Wolfgang Thaller
* 5.5  : Added `FinalizerEnvPtr', `newForeignPtrEnv', and
 `addForeignPtrFinalizerEnv'
* 6.3  : Added John Meacham proposal for `wchar_t' support as well localised
 string marshalling; in particular, this adds `CWString' and
 `CWStringLen' as well as the `CWString' and the `CAString' family
 of marshalling routines.  In addition, `charIsRepresentable' was
 added. 
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: H98 FFI Addendum 1.0, Release Candidate 15

2003-11-13 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote,

  And here now a probably naive question of mine: Does the
  notion of Marlow sensibility coincide with platforms that
  follow ISO/IEC 10646?
 
 We don't want to restrict the standard to sensible systems, because that
 rules out Windows :-).  

What a nice definition of sensible systems ;-)

 So, the standard should say that the system converts appropriately
 between Haskell's Unicode Char and whatever the system's encoding for
 wchar_t is.  We don't want castCharToCWchar, because the encoding of a
 Char into wchar_t might result in multiple wchar_ts.

Ok.  This seems to coincide what John wrote in his reply to
my message.

The spec at the moment says,

  To simplify bindings to C libraries that use
  \code{wchar\_t} for character sets that cannot be encoded
  in byte strings, the module \code{CString} also exports a
  variant of the above string marshalling routines for wide
  characters.

How shall this text be amended?  Is the following
sufficient?

  These marshalling routines convert Haskell's Unicode
  representation for characters into the platform-specific
  encoding used for \code{wchar\_t} and vice versa.  In
  particular, on platforms that represent \code{wchar\_t}
  values according to the encoding specified by ISO/IEC
  10646, this conversion reduces to a simple type cast
  without any alteration of the character values.  For all
  other platforms, the exact rules of the conversion are
  platform-specific and not further defined in this report.

Does anybody have any suggestions for improving this
explanation?

Cheers,
Manuel

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


ANN: H98 FFI Addendum 1.0, Release Candidate 15

2003-11-11 Thread Manuel M T Chakravarty
Release Candidate 15 with all the changes discussed since
RC13 is now available from

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

The only open problem are a set of questions raised by Simon
and Ross to which I have previously answered with another
set of questions (see the attached message), which is were
the discussion stopped.  In order to get it going again, I
propose the following:

* We require from a FFI library implementation only that it
  supports CWString and the associated functions on
  platforms, which are Marlow sensible.

* On other platforms a FFI library is free to do what it
  wants (eg, not support these functions at all or attempt
  to implement something similar).

And here now a probably naive question of mine: Does the
notion of Marlow sensibility coincide with platforms that
follow ISO/IEC 10646?

Cheers,
Manuel

-=-

Changes since RC14:
* 6.2: CWChar - CWchar
* 6.3: - CWChar - CWchar
   - Stated explicitly that memory allocated by `newCString' and friends
 can be deallocated by `MarshalAlloc.free'
   - Improved documentation

Changes since RC13:
* 5.3: Fixed typo
* 5.7: Fixed a mistake in the type of `peekByteOff' and `pokeByteOff' (the
   type variable constrained by `Storable' must be different from the
   parameter of the `Ptr')
* 6.3: Improved documentation
---BeginMessage---
Simon Marlow [EMAIL PROTECTED] wrote,

  I have put RC 14 at
  
http://www.cse.unsw.edu.au/~chak/haskell/ffi/
  
  including all the feedback on RC13.  Please especially have
  a look at Section 6.3 (Section CString), where some of the
  wording changed.
 
 The spec is silent on how exactly a Haskell Char is translated to a
 CWchar, and there aren't any conversion functions ala castCharToCCHar /
 castCCharToChar.

Hmm, should we maybe have a `castCharToCwchar' and `castCwcharToChar'?

 So presumably the expected behaviour is that the implementation does its
 best to translate between Unicode Char and whatever encoding the
 prevailing C library is using for wchar.  Any sensible implementation
 will be using Unicode for wchar too, so the translation will be a simple
 no-op, but the C standard doesn't specify this.  Older systems will
 probably have a locale-dependent encoding for wchar.  The GNU C library
 has a slight bug in this regard, too (see previous discussion).
 
 I expect that when we implement the CWString operations for GHC we won't
 bother with any locale-dependent translations, so the implementation
 will only work on sensible systems.
 
 There is a fair bit that is non-obvious here, so I feel the spec ought
 to say something.

Yes, I agree.  The question is, what do we actually want for
the standard?  Do we want to restrict the standard to only
work for sensible systems?  If so, what is the proper
phrase to identify sensible systems?

Cheers,
Manuel

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


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

2003-11-05 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote,

  I have put RC 14 at
  
http://www.cse.unsw.edu.au/~chak/haskell/ffi/
  
  including all the feedback on RC13.  Please especially have
  a look at Section 6.3 (Section CString), where some of the
  wording changed.
 
 The spec is silent on how exactly a Haskell Char is translated to a
 CWchar, and there aren't any conversion functions ala castCharToCCHar /
 castCCharToChar.

Hmm, should we maybe have a `castCharToCwchar' and `castCwcharToChar'?

 So presumably the expected behaviour is that the implementation does its
 best to translate between Unicode Char and whatever encoding the
 prevailing C library is using for wchar.  Any sensible implementation
 will be using Unicode for wchar too, so the translation will be a simple
 no-op, but the C standard doesn't specify this.  Older systems will
 probably have a locale-dependent encoding for wchar.  The GNU C library
 has a slight bug in this regard, too (see previous discussion).
 
 I expect that when we implement the CWString operations for GHC we won't
 bother with any locale-dependent translations, so the implementation
 will only work on sensible systems.
 
 There is a fair bit that is non-obvious here, so I feel the spec ought
 to say something.

Yes, I agree.  The question is, what do we actually want for
the standard?  Do we want to restrict the standard to only
work for sensible systems?  If so, what is the proper
phrase to identify sensible systems?

Cheers,
Manuel

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


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

2003-11-02 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote,

  I wonder how this discrepancy between the libraries and the
  report arose. 
 
 For what it's worth, the library has been that way since June 28, 2001:
 
 http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/base/Foreign/
 Storable.hs?rev=1.1content-type=text/x-cvsweb-markup
 
 http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/base/GHC/
 Storable.lhs?rev=1.1content-type=text/x-cvsweb-markup
 
 This seems to be copied from Marcin's QForeign which had the same type from 
 Jan 2, 2001 - March 18, 2001 (i.e., the entire lifetime of the library)
 
 http://cvs.sourceforge.net/viewcvs.py/qforeign/qforeign/lib/
 QStorable.hsc?rev=1.7view=markup
 
  Did I simply make a mistake when writting the
  report (then, this would qualify as an error in the report
  anyway)?
 
 On this evidence, it looks like it's an error in the report.

I agree.  I am changing the report.  Thanks for the
forensics.  And thanks to Sven for spotting the mismatch.

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


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

2003-11-02 Thread Manuel M T Chakravarty
Ross Paterson [EMAIL PROTECTED] wrote,

 In the sentence
 
   The marshalling takes the current Unicode encoding on the
   Haskell side into account.
 
 (which seems to have been there before), current seems wrong, since
 the Haskell side is constant.  How about something like
 
   The marshalling converts each Haskell character, representing
   a Unicode code point, to one or more bytes in a manner
   determined by the current locale.
 
 and dropping the later sentence about the locale.

Done.

 It might be worth emphasizing that the Len is the number of bytes
 rather than Chars.

Done.

 In the part about the single-byte versions, it might be worth tightening
 the warning to say that these preserve only the first 256 values of Char.

Ok.

 (That is the Latin-1 subset, so calling them ASCII seems a misnomer.)

Yes, but we can't call it Latin-1 either, because that
implies a locale (there is also Latin-2 etc).

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


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

2003-11-02 Thread Manuel M T Chakravarty
John Meacham [EMAIL PROTECTED] wrote,

 On Fri, Oct 31, 2003 at 12:32:55PM +, Ross Paterson wrote:
  Making the Right Thing the default, though it may cost more, seems
  appropriate.
  
  In the sentence
  
  The marshalling takes the current Unicode encoding on the
  Haskell side into account.
  
  (which seems to have been there before), current seems wrong, since
  the Haskell side is constant.  How about something like
  
  The marshalling converts each Haskell character, representing
  a Unicode code point, to one or more bytes in a manner
  determined by the current locale.
  
  and dropping the later sentence about the locale.
 
 This sounds good to me. I also might reword the paragraph introducing
 the 8bit versions, as the efficiency reason for using them is less
 important than the API one. meaning that some C APIs specify that a
 localized string should be passed, while others explicitly don't use
 localization and only expect ASCII (or another specific encoding such as
 utf8) strings and this is most likely what will determine the choice of
 string marshalers. 

True.  I changed that.

  What happens if one attempts to convert a Char that has no encoding
  in the current locale?
 
 my implementation converts unrepresentable characters to '?'. But
 a case could be made for throwing a CharsetConversion exception of some
 sort or simply eliding invalid characters. I am not sure what is best, I
 chose the '?' route because it matches what happens when you don't have
 a font installed and get a replacement character and is less troublesome
 for the user.  

I agree.  I now documented to conversion to '?'.

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


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

2003-11-02 Thread Manuel M T Chakravarty
I have put RC 14 at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

including all the feedback on RC13.  Please especially have
a look at Section 6.3 (Section CString), where some of the
wording changed.

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


ANN: H98 FFI Addendum 1.0, Release Candidate 12

2003-08-01 Thread Manuel M T Chakravarty
Dear Haskell Folks,

Release Candidate 12 of the H98 FFI Addendum 1.0 is now
available from

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

Since the release of RC 11 (12 June), there was only one
small change (which was already under discussion before RC
11 was published).  Hence, I consider Version 1.0 of the FFI
Addendum to be completed; no changes except linguistic ones
and plain error corrections will be accepted anymore for
this version.

Cheers,
Manuel

-=-

Changes since RC11:
* 5.5: Swapped argument order of `newForeignPtr' and `addForeignPtrFinalizer'

Note to FFI people, there were at least three votes
(Alastair, Sven, and me) for this change and none against.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: new ForeignPtr without finalizers

2003-06-12 Thread Manuel M T Chakravarty
Dean Herington [EMAIL PROTECTED] wrote,

 On Thu, 12 Jun 2003, Alastair Reid wrote:
 
  Manuel:
   In other words, it seem much more likely that one would
   partially apply `newForeignPtr' to a finaliser than to a
   pointer that is to be finalised.  But this is a minor point.
  
  Having written some more ffi code over the last couple of days, I agree that 
  this is much more natural so, even though it will break all the packages I 
  released in the last week, I now vote for swapping the argument order.
  
  Since this breaks code anyway, we could adopt Dean's proposal to allow lists 
  of arguments to newFP and addFPFinalizers without making things worse.  I 
  don't think we should do this though since I believe they would always be 
  used with singleton or empty arguments and because the list-based versions 
  can be trivially added with a foldM if they prove useful.
 
 Actually, I think I prefer Ashley's idea of separating the creation of a 
 ForeignPtr from the addition of a FinalizerPtr.  So how about:
 
 newForeignPtr  :: Ptr a - IO (ForeignPtr a)
 addForeignPtrFinalizer :: FinalizerPtr a - ForeignPtr a - IO ()
 
 newForeignPtrWithFinalizer :: FinalizerPtr a - Ptr a - IO (ForeignPtr a)
 newForeignPtrWithFinalizer f p = do p' - newForeignPtr p
 addForeignPtrFinalizer f p'
 return p'

This is what is in RC 11, just with other function names.

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


Re: new ForeignPtr without finalizers

2003-06-11 Thread Manuel M T Chakravarty
Dean Herington [EMAIL PROTECTED] wrote,

 Alastair Reid wrote:
 
  I'm not convinced that merging them into a single function is desirable, but,
  if we wanted to, I think a better FPish solution is to use
 
Maybe (FinalizerPtr a)
 
 As multiple finalizers are allowed, perhaps we should consider:
 
 newForeignPtr :: [FinalizerPtr a] - Ptr a - IO (ForeignPtr a)
 addForeignPtrFinalizers :: [FinalizerPtr a] - ForeignPtr a - IO ()

True, but it would also break old code and I doubt that
users would often add more than one finaliser at a time.

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


Re: new ForeignPtr without finalizers

2003-06-11 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote,

  I'd propose to
 
  * add `newForeignPtr_',
  * reverse the argument order to `newForeignPtr', and
  * reverse the argument order to `addForeignPointerFinalizer'
(for consistency).
 
 I agree with adding newForeignPtr_.  (Presumably the report would define 
 newForeignPtr in terms of newForeignPtr_ and addForeignPtrFinalizer.)
 
 I'd prefer to avoid swapping the argument order because of code breakage.

I think, we all agree on adding `newForeignPtr_' (so, I'll
add that).  The reason why I suggested reversing the
argument order is that

  newForeignPtr_ :: Ptr a - IO (ForeignPtr a)

and with *reversed* arguments also

  newForeignPtr myFinalizer :: Ptr a - IO (ForeignPtr a)

In other words, it seem much more likely that one would
partially apply `newForeignPtr' to a finaliser than to a
pointer that is to be finalised.  But this is a minor point.

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


Re: new ForeignPtr without finalizers

2003-06-09 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote,

 Ashley:
  How do I create a new ForeignPtr that doesn't have any finalizers?
 
 Malcolm:
  Why would you want to?
 
 addForeignPtrFinalizer lets you add them later.
 I'm guessing that Ashley is making heavy use of this ability.
 
 [What we have at the moment is the ability to attach a non-empty list of 
 finalizers to an object.  I don't immediately see a use for an empty list but
 my experience with various datatypes is that it is usually cleaner to allow 
 the empty or zero case and I#'m hoping that Ashley will demonstrate how it is 
 useful...]

Andre Pang here in his work to hook Haskell up with
ObjectiveC also found a need for foreign pointers without a
finalizer.  (Essentially, because there are two sorts of
foreign objects only one of which is reference counted, but
he otherwise wants to handle both sorts uniformly in the
binding.)

To create foreign pointers without a finalizer, I like
Alastair's

  newForeignPtr_ :: Ptr a - IO (ForeignPtr a)

Andre proposed to allow `nullFunPtr' as a finalizer argument
to `newForeignPtr' to indicate the lack of a finalizer.
This seems quite C-ish, but has the advantage that it is
easy to parametrise functions that internally use
`newForeignPtr' as to whether there should be a finalizer
attached.

I guess, the FP-ish solution is to pass an argument of type
`Ptr a - IO (ForeignPtr a)' which is `newForeignPtr_' if no
finalizers should be attached and is `newForeignPtr' already
applied to a finalizer if a particular finalizers is to be
attached.  However, then, it would be more convenient to
change the order of the two arguments to `newForeignPtr'.

Malcolm Wallace [EMAIL PROTECTED] wrote,

 Ashley Yakeley [EMAIL PROTECTED] writes:
 
  Specifically I want a ForeignPtr of a null Ptr that has no finalizers.
 
 Ah, this makes sense.
 I wonder if we should add the following to the FFI spec module ForeignPtr?
 
 nullForeignPtr :: ForeignPtr a-- a null pointer with null finalizer

This is easily implemented with `newForeignPtr_':

  nullForeignPtr = newForeignPtr_ nullPtr

Summary
~~~
I'd propose to

* add `newForeignPtr_',
* reverse the argument order to `newForeignPtr', and
* reverse the argument order to `addForeignPointerFinalizer'
  (for consistency).

Unfortunately, this is going to break code again.

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-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 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 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: ForeignPtr naming

2003-03-26 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote,

  As Haskell finalizers need pre-emptive concurrency, maybe
  they should go somewhere related to concurrency.  Or we
  could have a Foreign.Concurrent.
 
 Ok, how about Foreign.Concurrent.newForeignPtr and
 Foreign.Concurrent.addForeignPtrFinalizer?  i.e. dodging the naming
 issue by using the module system.  It also means that code which uses
 GHC's existing versions of these functions can be fixed by changing
 imports only.

Sounds good to me.

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


Re: Comparing [Fun]Ptrs

2003-03-05 Thread Manuel M T Chakravarty
Volker Stolz [EMAIL PROTECTED] wrote,

 Hi, I'm looking for a way of comparing Ptrs to null *elegantly*.
 The FFI distinguishes between 'Ptr a' and 'FunPtr a', so testing
 would mean writing ((==) null[Fun]Ptr). This is rather tedious and a predicate
 'isNull' might be in order so that it's possible to write
 
when (isNull p) $ ...
 or
throwIOErrorIf isNull ...
 , especially without having to worry about comparing against the correct
 null pointer (FunPtr or Ptr). That's something where a class can help, but
 I'm not sure whether such a specialised class is desired...

An isNullPtr was proposed before and rejected; see the
corresponding thread in the archive of this list.  Mainly on
the grounds that people didn't consider ((==) null[Fun]Ptr)
to be tedious to write.

Besides, I really don't want to make any changes for version
1.0 of the spec anymore; except finish up the
finalizer/Foreign{Ptr,Proxy} story.  Further convenience
functions can go into extra libraries (there is no need to
stick them all in the base spec).

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


Re: Foreign import

2003-03-04 Thread Manuel M T Chakravarty
Gustavo Villavicencio [EMAIL PROTECTED] wrote,

 I'm a new ffi user and I have some problems with foreign import
 declaration. I'm don't have any problem to access C standard functions.
 However, I cannot access to my own functions in mylib.h by means of
 
 foreign import mylib.h myfun hmyfun :: ...
 
 May be I'm omitting some compilation step or parameter also, since I'm
 applying the same compilation process to call C standard functions.
 
 I'm working with ghc 5.04 on SuSe Linux 7.0.

You should say what goes wrong.  Eg, paste the error
messages of the compiler and/or linker into your email.

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


Re: [GUI] Example: Binding C++ to Haskell using the ffi

2003-03-02 Thread Manuel M T Chakravarty
David Sankel [EMAIL PROTECTED] wrote,

 for the ffi people:
 
 Has any though gone into cplusplus?  If so, how would
 it interface?  Would stubs on the c++ side be
 generated or would it use the code directly.

Interfacing in a clean and comprehensive way to OO languages
is hard.  For a discussion of some of the problems wrt to
typing, see

  http://research.microsoft.com/Users/simonpj/Papers/oo-haskell/

AFAIK, nobody is currently actively working on a FFI
extension for C++ or Java.

Cheers,
Manuel



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


Re: Repeated hs_init()/hs_exit()

2003-02-10 Thread Manuel M T Chakravarty
Fergus Henderson [EMAIL PROTECTED] wrote,

 On 28-Jan-2003, Simon Marlow [EMAIL PROTECTED] wrote:
  I'm implementing the latest hs_init()/hs_exit() interface in GHC, and
  came across an ambiguity or omission in the spec.  We're clear that this
  sequence should be allowed:
  
hs_init(..)
hs_init(..)
hs_exit()
hs_exit()
  
  but what about
  
hs_init(..)
hs_exit()
hs_init(..)
hs_exit()
  
  That is, should the Haskell system be able to start itself up again
  after shutting down?  It looks like this is desirable from a modularity
  viewpoint: eg. a C program initialises library A which uses Haskell
  internally, then de-initialises library A, then initialises library B
  which also uses Haskell internally.
  
  Unfortunately, this is going to require quite a bit of extra work in GHC
  to get right, and it looks like I'm going to have to examine a lot of
  code to make sure it is double-init-safe.  Thoughts?
 
 FWIW, getting this sort of thing to work properly with the Mercury
 implementation would also be quite a lot of work.
 
 Still, I do think that this sort of thing should be supported.
 Sometimes standards should serve to advance the state of the art,
 rather than merely standardizing on the flaws of existing
 implementations, and I think this is one of those time.s

Ok.  I will add to the spec that complete de-initialisation
followed (re)initialisation should be supported.

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



Re: safe and threadsafe

2003-02-10 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote,

  I don't think it was ever the intention that 'safe' should have a
  guaranteed serialisation property.  I think the idea was that
  'threadsafe' was the most desirable, with 'safe' and 'unsafe' only
  available for use if you wanted more efficiency and had some separate
  guarantees that the extra efficiency was not at the expense of
  correctness.
  
  To be completely explicit, I think that increasing the safety level of
  any foreign import should never make the program fail.
 
 If I recall correctly, the motivation for keeping safe was that we
 wanted to be able to make calls into non-threadsafe C libraries.  Which,
 incedentally, would break the property that Simon mentions above: a
 non-threadsafe library would *require* foreign imports to be labelled
 safe rather than threadsafe.
 
 However, at the time I don't think we appreciated the implementation
 diffiulties arising from safe.  Also, Wolfgang has pointed out that
 you can simulate serialisation in Haskell using MVars.

With the MVar solution, I am worried that it will add a lot
of extra code to large libraries like Gtk+HS, where every
single of the hundreds of functions would need to be
protected by an MVar.  Hence, to answer Wolfgang's question

Wolfgang Thaller [EMAIL PROTECTED] wrote,

 Are safe calls _guaranteed_ to block all other haskell threads and 
 prevent garbage collection,
 or is that an implementation detail? Are unsafe calls guaranteed to do 
 so?

My intention was that safe and unsafe calls are guaranteed
to block Haskell threads.  Consequently, safe and threadsafe
shouldn't be collapsed into one.

Reading Wolfgang's description of how the various policies
are implemented, I actually got a bit worried about
efficiency in general.  How much more expensive than a
vanilla function call is an unsafe, a safe, and a threadsafe
call in the threaded RTS at the moment?

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



Re: cids and fnames in ccall impents

2003-01-22 Thread Manuel M T Chakravarty
Ian Lynagh [EMAIL PROTECTED] wrote,

 On Wed, Nov 06, 2002 at 12:04:22AM +, Ian Lynagh wrote:
  On Tue, Nov 05, 2002 at 09:53:52PM +, Alastair Reid wrote:
   
   If it isn't spelled out explicitly already, it would be good to do that.
  
  How about something like this?
  
  Maximal munch applies.
  
  token - special |  | fname | cid | whitespace
  special - static | dynamic | wrapper
  fname - ... .h  (... as I don't have [3] handy)
  cid - ... excluding special   (... as I don't have [3] handy)
 
 [3] tells me that cid is [_a-zA-Z][_a-zA-Z0-9]* (which I think should be
 in the FFI spec itself too) but I can't find a definition of fname in
 it.
 
 The C99 spec allows a lot of stuff I don't think makes sense after
 #include, but a header file is specified by either [^\n]+ or
 [^\n]+. This only seems sensible if the  or  are also in the
 impent string which is not the case in the examples.
 
 Can someone clarify the intention for me please (and preferably also do
 so in the FFI spec)?

I have now included a formal definition of the two
nonterminals in Section 2 (Lexical Structure) of the FFI
report.  I append the text below.  cid is defined to be
[_a-zA-Z][_a-zA-Z0-9]* (as you wrote above).  However,
chname (which now replaces fname) produces only a subset of
those lexemes admitted by C99.  I don't think there would be
much point in trying to exactly mirror C99, as more
complicated header file arrangements require a special
purpose C header file for Haskell bindings anyway.

Cheers,
Manuel

-=-

To refer to objects of an external C context, we introduce the following
phrases:
%
\begin{grammar}
  \grule[C header filename]{chname}{%
\grepeat{\gnterm{chchar}} .\ h}
  \grule[C identifier]{cid}{%
\gnterm{letter} \grepeat{\gnterm{letter} \galt\ \gnterm{ascDigit}}}
  \grule{chchar}{%
\gnterm{letter} \galt\ \gnterm{ascSymbol}\gminus{\}}
  \grule{letter}{%
\gnterm{ascSmall} \galt\ \gnterm{ascLarge} \galt\ \_}
\end{grammar}
%
The range of lexemes that are admissible for \gnterm{chname} is a subset of
those permitted as arguments to the \code{\#{}include} directive in C.  In
particular, a file name \gnterm{chname} must end in the suffix \code{.h}.  The
lexemes produced by \gnterm{cid} coincide with those allowed as C identifiers,
as specified in~\cite{C}.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



ANN: H98 FFI Addendum 1.0, Release Candidate 8

2003-01-22 Thread Manuel M T Chakravarty
I put a snapshot of the current status of the FFI Addendum
as RC8 at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

Despite there still being two unfinished discussion threads,
I felt that it is time for another RC, as many people
probably don't track the progress in CVS.

Cheers,
Manuel

-=-

% Changes since RC7:
% * Clarified the lexis of C identifiers and C header file names
% * In `ForeignPtr', added `mallocForeignPtrArray' and `mallocForeignPtrArray0'
% * Clarified spec of allocations functions adding constraints taken from the
%   corresponding C routines
% * `mallocBytes' and `allocaBytes' must align memory sufficiently for any
%   basic foreign type that fits into the allocated block
% * Removed typos in the description of the module `ForeignPtr'
% * Added Peter Gammie to the list of acknowledged people
% * `addForeignPtrFinalizer' guarantees that finalizers for a single foreign
%   pointer are executed in the opposite order as they were added.
% * `Storable': Require that the size is divisible by the alignment
% * Added Ross Paterson to the list of acknowledged people
% * Added hs_free_fun_ptr() and hs_free_stable_ptr()
% * Changed order of arguments of `mkIOError' and `annotateIOError' to match
%   with the current implementation in GHC's FFI libraries.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Re-exporting modules in the Foreign hierarchy

2003-01-21 Thread Manuel M T Chakravarty
Malcolm Wallace [EMAIL PROTECTED] wrote,

 I do seem to remember a proposal at one stage to remove Foreign.C.TypesISO
 altogether by incorporating it fully into Foreign.C.Types.  Given that
 the latter re-exports everything from the former, is there any reason
 for TypesISO to remain separate?

CTypesISO has been removed from the FFI spec a while ago.
It should be removed from the implementation, too.

Cheers,
Manuel

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



Re: Finalizers finalized

2003-01-21 Thread Manuel M T Chakravarty
Ross Paterson [EMAIL PROTECTED] wrote,

 On Fri, Jan 17, 2003 at 10:23:27AM +1100, Manuel M T Chakravarty wrote:
  Ross Paterson [EMAIL PROTECTED] wrote,
  
   I'd also like to see the addition of
   
 mallocForeignPtrArray :: Storable a = Int - IO (ForeignPtr a)
   
   to ForeignPtr, to save people from rolling their own.  (Maybe the realloc
   and 0 versions too?)
  
  The reason I didn't answer to this earlier is that I wanted
  to see how many people say that they support this addition.
  To be honest, I never needed a function like this.  Did
  anybody else?
 
 Only me, it seems.  But surely if both mallocForeignPtr and mallocArray
 are useful, this is too.

 If you don't want to do explicit deallocation, mallocForeignPtr is
 attractive (and handled specially by GHC).  Sooner or later there are
 going to be arrays, and then if there's no such function you'll have to
 write your own.

Yes, I think you are right that an orthogonality argument
can be made here.  So, let's add the function.  I assume
from the silence on this topic that nobody has an serious
objections to adding this function.
`mallocForeignPtrArray0' should then also be added, as you
say.

I am not so sure about a realloc version.  It, at least,
requires some care, as realloc may return a pointer different
from the original.  (In other words, there is no guarantee
that realloc works in-place.)  I just noticed that the spec
doesn't mention this; so, I'll add it.  We should also
include the special cases that the C library covers:

* If `realloc' is passed a `nullPtr', it works like
  `malloc'.

* If the size requested from `reallocBytes' is 0, it works
  like `free'.

Finally, I am not sure whether we really want to allow that
`reallocBytes' may be used on `alloca'ed memory, which the
spec currently explicitly admits.


Proposed changes


Add to `ForeignPtr':

  mallocForeignPtrArray  :: Storable a = Int - IO (ForeignPtr a)
  mallocForeignPtrArray0 :: Storable a = Int - IO (ForeignPtr a)

Refine spec of `MarshalAlloc' as follows:

* realloc may return a pointer other than the one passed in.
  State special cases for passing `nullPtr' and size of 0,
  respectively, to `realloc' as stated above.

[I will already apply these changes.]


Open questions (feedback requested)
~~

* Shall we remove the sentence allowing `reallocBytes' on
  `alloca'ed memory?

* Shall we provide reallocForeignPtrArray and
  reallocForeignPtrArray0? 

[I will not apply these changes until after further
discussion.] 

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



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

2003-01-21 Thread Manuel M T Chakravarty
Ross Paterson [EMAIL PROTECTED] 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
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



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

2003-01-20 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote,

  perhaps ForeignPtr should not be an instance of Eq so people can
  provide their own?
 
 Note that if we did this, we'd want to consider adding an operation
 
   eqForeignPtr :: FP a - FP a - Bool 
 
   FP b-- possible variant but not very useful
 
 which lets people test equality of the container and not the contents.
 
 In fact the more I think on it, the more convinced I am that the Eq
 instance should compare contaner equality and not contents equality.
 The reason is that I believe Eq instances should follow the following
 design rule:
 
  Eq instances should compute observational equivalence
 
 I believe this is satisfied by all Haskell98 types, all the usual
 extensions (IORefs and friends) and by derived instances of datatypes.

So far, I agree.

 Just to be clear what I mean by observational equivalence, consider
 comparing two IORefs x and y using this code:
 
 eq x y = do
   a - readIORef x
   writeIORef (a+1)
   b - readIORef x
   return (x==y)
   
   Obviously, this code is a bad way to test if two IORefs are the same
   IORef but the point is that we can observe the difference between
   them.  Similarily, with ForeignPtrs, adding a finalizer to one and not
   the other and then watching for when the finalizer runs is a way that
   we might observe differences between two FPs.

There is no way in H98 + FFI to observe that a finalizer has
run.  In fact, in the finalizer discussion your point was
that any means to observe this would lead to races.

 What I don't mean by observational (in)equivalence is this:
 
   One might be able to distinguish two data structures of type [Int]
   (say), by observing how much memory they consume.
 
 This is perfectly true but Haskell semantics doesn't let you observe
 this so we'll rule any such 'observations' as irrelevant or invalid.

In C, we can observe it, and only in C can we observe whether
a finalizer was executed.

Nevertheless, your point regarding observations is an
important one.  We must not be able to observe a change in
the equality of two values.  This is why we cannot define
equality of IORef's as the contents of the IORef's.
However, the contents (ie, vanilla pointer on which it is
based) of a ForeignPtr can never change.  Hence, defining
the equality of ForeignPtrs via their contents is perfectly
valid. 

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.

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



Re: Proposal: Pooled memory management

2003-01-19 Thread Manuel M T Chakravarty
Sven Panne [EMAIL PROTECTED] wrote,

 The FFI libraries currently contain support for explicit allocation
 and deallocation via the malloc/free family and support for implicit
 allocation and deallocation via alloca and friends. But there is a
 very useful level between these extremes: Pooled memory management.
 Under this scheme, (re-)allocations belong to a given pool, and
 everything in a pool is deallocated when the pool itself is
 deallocated.

To be honest, I am reluctant to add this module to the FFI
addendum.  This is not to say that the module may not be
useful and may not be a worthwhile addition to the library
hierachy.  Here are my reasons:

* I want to get v1.0 of the spec fixed.  We are really only
  in bug fix mode for quite a while and only the finalizer
  problems held us back from finishing the spec.

* I am sure there are plenty more useful FFI-related
  libraries.  However, the initial plan was to define basic
  functionality on top of which more elaborate schemes can
  be implemented.  We need to draw the line somewhere.

In particular, I don't want to add a largely untested
library.

So, I propose to add Pool to the portable libraries package,
but leave it out of the spec.

Cheers,
Manuel

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



Re: alignment

2003-01-14 Thread Manuel M T Chakravarty
Ross Paterson [EMAIL PROTECTED] wrote,

 On Mon, Jan 13, 2003 at 09:00:33PM +1100, Manuel M T Chakravarty wrote:
  Fergus Henderson [EMAIL PROTECTED] wrote,
  
   On 09-Jan-2003, Ross Paterson [EMAIL PROTECTED] wrote:
Two additions I think are required:

1) The spec should state that mallocBytes and allocaBytes return a block
   of memory sufficiently aligned for any of the primitive types supported
   by the architecture.
   
   I disagree.  These routines should only be required to align the memory
   sufficiently for any of the primitive types which could fit in the amount
   of space allocated.  For example, double precision floats might occupy
   8 bytes, and require 8-byte alignment, but four-bytes allocations should
   not be required to be 8-byte aligned.
   
   (This is something the C standard got wrong, IMHO.)
  
  I agree with Fergus.
 
 Yes, that's even better: a C malloc will satisfy this constraint, but so
 will others.

It now requires,

  The block of memory is sufficiently aligned for any of the
  basic foreign types (see Section~\ref{sec:foreign-types})
  that fits into a memory block of the allocated size.

  \item[sizeOf::\ Storable a = a - Int]
  \item[alignment~::\ Storable a = a - Int]\combineitems
[...]  We require that all
the elements of a contiguous array of storable values meet the alignment
constraint of these values; more formally, we require that
%
\begin{quote}
  \begin{verbatim}
  sizeOf v `mod` alignment v == 0
  \end{verbatim}%
\end{quote}
 
 How about just:
 
   We require that the size is divisible by the alignment.
   (Thus each element of a contiguous array of storable values
   will be properly aligned if the first one is.)

Ok, I am using your more concise wording.

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



Re: alignment

2003-01-13 Thread Manuel M T Chakravarty
Fergus Henderson [EMAIL PROTECTED] wrote,

 On 09-Jan-2003, Ross Paterson [EMAIL PROTECTED] wrote:
  Two additions I think are required:
  
  1) The spec should state that mallocBytes and allocaBytes return a block
 of memory sufficiently aligned for any of the primitive types supported
 by the architecture.
 
 I disagree.  These routines should only be required to align the memory
 sufficiently for any of the primitive types which could fit in the amount
 of space allocated.  For example, double precision floats might occupy
 8 bytes, and require 8-byte alignment, but four-bytes allocations should
 not be required to be 8-byte aligned.
 
 (This is something the C standard got wrong, IMHO.)

I agree with Fergus.

Ross Paterson [EMAIL PROTECTED] wrote,

 2) The description of Storable should require
 
   sizeOf x `mod` alignment x = 0
 
The library implementation of mallocArray implicitly assumes this, and
C also requires that elements of an array are allocated contiguously.

Ok.  I attach the amended description of these functions.

Thanks,
Manuel

-=-

\item[sizeOf::\ Storable a = a - Int]
\item[alignment~::\ Storable a = a - Int]\combineitems The function
  \code{sizeOf} computes the storage requirements (in bytes) of the argument,
  and alignment computes the alignment constraint of the argument.  An
  alignment constraint \code{x} is fulfilled by any address divisible by
  \code{x}. Both functions do not evaluate their argument, but compute the
  result on the basis of the type of the argument alone.  We require that all
  the elements of a contiguous array of storable values meet the alignment
  constraint of these values; more formally, we require that
  %
  \begin{quote}
\begin{verbatim}
sizeOf v `mod` alignment v == 0
\end{verbatim}%
  \end{quote}
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Finalizers: conclusion?

2003-01-13 Thread Manuel M T Chakravarty
Antony Courtney [EMAIL PROTECTED] wrote,

 You indicated that you were somewhat unclear why we need liveness 
 dependencies.  I'll attempt to clarify by sketching some of the details 
 of the particular C library for which I am writing FFI wrappers.
 
 I have a C library for 2D vector graphics.  Two of the abstract types 
 provided by this C library are:
 Pixmap -- A handle to an actual buffer of raster data
 RenderContext -- A handle that encapsulates all state associated 
 with rendering, such as the current color, current font, target pixmap, etc.
 
 Note that it is possible to create many RenderingContext's that all 
 render on to the same underlying Pixmap.
 
 To see why we need liveness dependencies, consider the following typical 
 usage scenario in Haskell:
 do pm - createPixmap   -- 1
rc - createRenderContext pm -- 2
drawBox rc   -- 3
...
 
 Note that, in the above, it's possible that the call to 
 createRenderContext in line 2 could be the last Haskell reference to pm, 
 making it a candidate for collection.  But we don't actually want the 
 Pixmap to be collected (and its finalizer invoked) until both the Pixmap 
   *and* all associated rendering contexts which refer to the Pixmap 
 become unreachable.
 
 The reason we need liveness dependencies is because, internally, the 
 RenderContext maintains a pointer to the target Pixmap.  But because 
 this pointer exists only in the C heap, we need some way to inform 
 Haskell's garbage collector that whenever a particular RenderContext is 
 reachable, then its target pixmap is also reachable.

IMHO you are trying to compensate for a flaw in the whole
setup:

* Line 1: You get a pointer to a C object assuming it is the
last reference to that C object.

* Line 2: You pass this pointer back to C without copying
it; ie, the only reference to the C object is in C land.

At this moment, the pointer obtained on Line 1 is no longer
the business of the Haskell system.  It is a pointer in C
land to a C object; so, memory management of that structure
should be let to the C library.  Assume the following C
function

  RenderContext *createPixmapWithContext ()
  {

Pixmap *pm = createPixmap ();
return createRenderContext (pm);
  }

in conjunction with

  do
rc - createPixmapWithContext
drawBox rc

How is this different from your Haskell code in a way that
requires a foreign pointer dependency in one case, but not
in the other?

The only answer that I can think of is that when you passed
the reference back to C (and hence, the responsibility to
eventually free the object), you already registered a
finalizer on `pm', which will run eventually (as there is no
way of getting rid of it without running it).  Hence, you
want to delay running it.  My point is that running this
finalizer (if it deallocated the object) is wrong at any
time: As `createPixmapWithContext()' demonstrates, C land
must free `pm' when the last render context referring to
`pm' dies.  Even if you delay running the Haskell finalizer
for `pm' after this (using `keepAlive' or so), it is still
wrong to deallocate the object twice.

IMO the only clean way to approach this problem is to add a
reference counting scheme to `pm' in C land.  Whenever `rc'
is deallocated it decrements the count on the `pm' it refers
to.  Similarly, the finalizer on `pm' calls the routine that
decrements reference counts.  As usual, the object is only
deallocated when its reference count reaches zero.  BTW,
this is exactly how this problem is solved in the GTK+ GUI
toolkit.

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



Finalizers finalized

2003-01-13 Thread Manuel M T Chakravarty
Sorry for taking so awfully long with a wrap up of the
finalizer affair, but here it is.

Unanimous agreement:

* Alastair was right: Haskell finalizers require pre-emptive
  concurrency = C-finalizers only in FFI 1.0

Still under discussion:

* Names for the C-finalizer functions:

  - A number of people have called for names other than
those originally used for Haskell finalizers; in
particular, an inclusion of the word unsafe was
proposed.

  - Two important points have been ignored in this part of
the discussion:

(1) FFI RC 6 already included C finalizers *and* used
the original names (`newForeignPtr' and
`addForeignPtrFinalizer') after we discussed this
point before.

(2) Hugs Nov2002 already implements the FFI RC 6 API.
Alastair mentioned that before the release and
shortly after it was discovered that Haskell
finalizers won't make it into the FFI spec.

I think we owe it to the Hugs people to stick to
`newForeignPtr' and `addForeignPtrFinalizer' now.
Besides, I also think that these names are better.  As
Alastair mentioned, these are the only finalizer
primitives in the FFI, so it is a bit strange if they
are labeled unsafe.

Please also note that the unsafeness is different from
that in other functions that contain the word unsafe
(like `unsafePerformIO').  Hence, I don't think it would
really make the meaning clearer and being more precise
in the names would make them pretty long.

Proposed action: leave the names as published in FFI RC 6

* Alastair proposed the addition of

void hs_free_stable_ptr (HsStablePtr x);

  The name is consistent with the rest of the FFI C API and
  has already been included into Hugs Nov2002.  Moreover,
  Sven already added

void hs_free_stable_ptr (HsStablePtr *sp);
void hs_free_fun_ptr(HsFunPtr *fp);

  to the CVS version of the spec a while ago.  I am not sure
  whether the * in the signatures was a mistake.  Maybe
  the idea was to pass a pointer to the pointer that is to
  freed in and have the freeing function set that to 0L.
  However, I think, it is better to go with the interface
  suggested by free() and already implemented in Hugs.

  Proposed action: Add 

  void hs_free_stable_ptr (HsStablePtr sp);
  void hs_free_fun_ptr(HsFunPtr fp);

to the spec.

  [NB: Sven already added the functions with the * in the
  signature to GHC's `HsFFI.h'.  These would need to
  change.]

* Should there be a guaranteed execution order for multiple
  finalizers on a single object?  Alastair argues for this
  in

http://haskell.org/pipermail/ffi/2002-November/000990.html

  There have neither been positive nor negative comments.

  Proposed action: Revise the spec for
`addForeignPtrFinalizer' to read as attached below.

* `touchForeignPtr', `keepAlive', and `ForeignDependency':
  To be honest, I don't buy into the motivation for
  `keepAlive' and friends from 

http://haskell.org/pipermail/ffi/2002-October/000942.html

  I'll state my reasons in a direct reply to the above
  message.

  Proposed action: leave `touchForeignPtr' as it is in FFI RC 6

* The `Proxy' story: The discussion seemed to have trailed
off without a real conclusion.  I'll write a seperate
email on this.

Any *serious* objections?  (I already executed the above
proposed actions on the CVS version of the spec.)

Cheers,
Manuel

-=-

\item[addForeignPtrFinalizer ::\ ForeignPtr a - FunPtr (Ptr a - IO ()) - IO
  ()] Add another finalizer to the given foreign pointer.  All finalizers
  associated with a single foreign pointer are executed in the opposite order
  of their addition---i.e., the finalizer added last will be executed first.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Foreign proxy

2003-01-13 Thread Manuel M T Chakravarty
An interface like the following has been repeatedly proposed
(in slightly varying versions):

  data ForeignObj a-- abstract
  instance Eq (ForeignObj a)
  
  type Finalizer a = FunPtr (a - IO ())
  
  newForeignObj   :: a - Finalizer a - IO (ForeignObj a) 
  addFinalizer:: ForeignObj a - Finalizer a - IO () 
  withForeignObj  :: ForeignObj a - (a - IO b) - IO b 
  touchForeignObj :: ForeignObj a - IO () 

If we adopt it, we might define `ForeignPtr' in terms of the
new interface:

  type ForeignPtr a = ForeignObj (Ptr a)
  newForeignPtr :: a - Finalizer (Ptr a) - IO (ForeignPtr a) 
  etc

We, btw, also need

  foreignObjToObj :: ForeignObj a - a

to implement `foreignPtrToPtr'.  Unfortunately, there
doesn't seem to be any easy way to implement
`castForeignPtr', which is valid for pointers, but can't be
generalised to `ForeignObj'.  We could assume the position
that such casts need always to be made on the vanilla `Ptr'
after it has been obtained from the `ForeignPtr'.  However,
this might be a nuisance in some situations.

Open Questions
~~

(1) Shall we adopt an interface like `ForeignObj'?  
(Seems like a nice idea to me.)

(2) What shall we do about `castForeignPtr'?

(3) Shall we call the new objects `ForeignObj'?
(It's a good name, but conflicts with some of GHC's
legacy libraries.  `ForeignProxy' is one of the more
appealing possible alternatives that was suggested
ealier.  `ForeignFinalized' is also nice, but maybe a
bit long.)

What do you think?

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



Re: C Struct Field Access

2002-10-17 Thread Manuel M T Chakravarty
Ashley Yakeley [EMAIL PROTECTED] wrote,

 What's the best strategy for accessing fields in someone else's C struct? 
 Should I write my own glue file with accessor functions? Or should I make 
 a Storable instance for the struct?

Well, my answer to this is the same as to Antony's C enum
question.  Specifically, see

  http://www.cse.unsw.edu.au/~chak/haskell/c2hs/docu/c2hs-3.html#ss3.8

Why do all the work yourself when a tool can do it for you?

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



Re: addForeignPtrFinalizer

2002-10-01 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

  I have to say that, given Simon's patch, I am inclined to revert
  back to the old API for foreign pointers.  
 
 I don't think such a change should be made unless Malcolm and I are
 able to implement it.  
 
 I'm not yet convinced that Simon's patch is as easy or correct as it
 seems and will not be until it has been heavily tested and until I
 have a chance to look carefully at the consequences of the change
 elsewhere in the system.  
 
 Also, Malcolm reported using a similar trick but that he couldn't get
 it to work reliably (i.e., it was ok if the finalizer did nothing but
 call out to C but not otherwise).

I won't change anything until we have finished discussing
the issue, but I got the impression that I probably rushed
the last change.  So, I wouldn't consider the current
definition the default either.

  The restriction on pure C land finalizers *is* awkward, and as we
  have already seen implies further changes (ie, adding something like
  `finalizerFree').
 
 We missed a small detail in specifying the change and fixed it when we
 went to implement it.  This happens with most design changes and
 doesn't seem like evidence of awkwardness to me.

Fair enough.  However, I still think that the current
definition is awkward.  It is awkward as it goes against the
spirit of the rest of the spec, which strives to accomplish
as much as possible in Haskell, not in C land.  It's awkward
as a user with a fairly big application (namely George) is
inconvenienced by it.  It's awkward because it requires a
subtle side condition on what is a valid finaliser that is
going to trip up users and cause strange errors.

This awkwardness is tolerable if it simplifies the
implementation a lot (as in avoids having to implement
pre-emptive concurrency).  It is not tolerable if it is just
a matter of verifying that an existing implementation
proposal does indeed work (or even if it requires tweaking
that proposal).

At least, this is my understanding of good language design.

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



Re: addForeignPtrFinalizer

2002-10-01 Thread Manuel M T Chakravarty

PS: Is everybody going to be at PLI'02?  Then, we could
discuss this face to face.

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



Re: FFI digest, Vol 1 #218 - 3 msgs

2002-09-30 Thread Manuel M T Chakravarty

George Russell [EMAIL PROTECTED] wrote,

 Simon Marlow wrote
  PS. I'm sorry to keep banging on about this.  Ultimately it doesn't
  really matter to me that much, since I only really use mallocForeignPtr.
  I guess I was just intrigued to see if the problem was really as
  difficult as we'd thought.
 [snip]
 I'm glad you are banging on about it.  But since it looks unlikely that there is 
going
 to be agreement on the matter, I suggest the following compromise.  We remove the
 restriction that finalizers may not call Haskell functions in the main body of the 
standard,
 but add a note that says that implementations may opt to impose such a restriction,
 provided they document it in some standard way.

That's as good as not defining it at all.  And given that
the type signatures of the two versions are different, it
isn't even a matter of imposing a runtime restriction.

Cheers,
Manuel

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



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

2002-09-21 Thread Manuel M T Chakravarty

Ross Paterson [EMAIL PROTECTED] wrote,

 Alastair Reid [EMAIL PROTECTED] 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.

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



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

2002-09-19 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

  RC 7 of the FFI Addendum is now available from
 
 In adding mallocForeignPtr and friends to Hugs, I found that I needed
 the address of free to pass as a parameter.
 
 There's no suitable way to generate free from MarshalAlloc.free (the
 obvious use of a Haskell wrapper would break the whole reason for the
 recent change to ForeignPtrs).
 
 Could we add free to the export list of MarshalAlloc?
 
   foreign import ccall unsafe stdlib.h free ptr_free :: FunPtr (Ptr a - IO ())
 
 I am currently using 'ptr_free' as the Haskell name for this pointer
 but I expect that a better name could be found with little effort.

So far, we never explicitly say (I believe) that `malloc'
corresponds to C's `malloc()'; ie, that C's `free()' (and
hence, `ptr_free') may actually be used to free storage that
has been allocated by `malloc'.

We might define the CAF

  cfree :: FunPtr (Ptr a - IO ())

as a pointer to a C function that free's storage allocated
with `malloc' from C without entering Haskell land and
explicitly note that this is useful as a finalizer.

The construction still seems pretty awkward to me.  I hope
the change to ForeignPtr doesn't entail any more nasty
suprises like this.

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



ANN: H98 FFI Addendum 1.0, Release Candidate 6

2002-09-12 Thread Manuel M T Chakravarty

Please review RC 6 available at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

A change log is appended.  This version features a rather
large number of changes over the last version, which is
making me a bit uneasy, as I hoped that the spec would
converge soon.  But many of these changes have been prompted
by Alastair and Malcolm bringing their systems in line,
which is probably the most effective way of debugging the
spec.

Cheers,
Manuel

-=-

* Author list: changed Alastair Reid's institution
* 1.4:   Clarified the wording
* 4.1:   Explicitly stated that access to pre-processor symbols is not
 provided by the FFI
* 4.1.1: Removed [lib] from impent syntax and discussion
* 4.1.3: Added parentheses round FunPtr ft to make it easier to 
 understand a tolerably complex type.
* 4.1.4: Removed all mention of library objects; clarified that header files
 do not impact the semantics of foreign calls, but may be required
 for correct code generation by some systems
* 5.2:   Clarified that all operations in Bits are member functions of the
 type class.  Reverse the meaning of the sign of the second argument
 for `rotate' and `shift' (this makes it the same as GHC used all
 the time).  `bitSize' on `Integer' etc is now undefined.
* 5.5:   Finalisers must be external functions to facilitate the
 implementation on Haskell systems that do not support pre-emptive
 concurrency.
 Added mallocForeignPtr and mallocForeignPtrBytes.
* 6: Specified that HsBool==int in table2
 Relabelled column 1 in table 3 (C symbol - CPP symbol)
 Replaced 0 and 1 with HS_BOOL_FALSE/TRUE
* 6.1:   Clarified that nullPtr (nullFunPtr) coincides with (HsPtr) NULL and
 (HsFunPtr) NULL, respectively.
 Allowing multiple calls to hs_init() and clarified the constraints
 on the relative timing between hs_set_argv() and
 getProgName/getArgs. 
 Added hs_perform_gc().
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: isNull{Fun,}Ptr

2002-09-11 Thread Manuel M T Chakravarty

Malcolm Wallace [EMAIL PROTECTED] wrote,

  Wolfram Kahl suggested to add functions isNullPtr and
  isNullFunPtr (with the expected semantics) to the Ptr
  module.  Opinions?
 
 Ptr and FunPtr are already instances of Eq, so which is easier to type?
 isNullPtr x
 or
 x==nullPtr
 
 So I don't see the motivation for the new predicates, but I don't have
 any objections either.

Sure, but there is also 

  null = (== [])

in the Prelude and `Maybe.isNothing'.  So, the reasoning for
adding these two functions would be that Haskell has a
tradition of providing predicates like this as alternatives
to the explicit use of (==).

Personally, I also don't care much in either direction.  Any
other opinions?

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



Re: module Data.Bits

2002-09-11 Thread Manuel M T Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

  The FFI Addendum actually doesn't commit to which operations
  are in the class.  It just says defines all these ops to
  have a context `Bits a', which is definitely the case.  In
  other words, you proposed implementation is valid by the
  spec and your argument for it makes sense to me.
 
 The spec really ought to say what the member functions of the class are,
 if we expect people to be able to define their own instances of Bits,
 and I don't see why we shouldn't allow that.

True.

 I think Malcolm's proposed change looks reasonable, although there was
 probably a reason why these functions weren't made class members in the
 first place.  Alastair: it was your design originally I believe, any
 thoughts?  I think it would be a small optimisation in GHC too, at least
 for shifts by non-constant amounts.

I applied Malcolm's change now.

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



Re: Updates to FFI spec: performGC

2002-09-11 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

 George Russell [EMAIL PROTECTED] writes:
  Also there are probably hard-real-time GC algorithms (like Baker's
  treadmill) or algorithms which are close to being hard-real-time
  (like the train algorithm) where doing a full GC would be a major
  pain.
 
 The desired property is that the runtime system releases all
 unreachable objects.  

I like that phrase, so I put

  Finally, \code{hs\_perform\_gc()} advices the Haskell
  storage manager to perform a garbage collection, where the
  storage manager makes an effort to releases all
  unreachable objects.  This function must not be invoked
  from C functions that are imported \code{unsafe} into
  Haskell code nor may it be used from a finalizer.

into the spec.  It's signals the intent, but still leaves an
implementation some freedom.

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



Re: Cheap ForeignPtr allocation

2002-09-11 Thread Manuel M T Chakravarty

I agree with SimonM that the proposed routines have useful
applications.  Furthermore, it is trivial for Haskell
systems to implement these routines.  Hence, I will include
them into the spec unless there are serious objections.

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



Re: Proposed change to ForeignPtr

2002-09-10 Thread Manuel M T Chakravarty

Manuel M T Chakravarty [EMAIL PROTECTED] wrote,

 We seem to have a consensus on this one.  We change the type
 of the existing functions to
 
   newForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)
   addForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO ()
 
 For GHC, I propose to put the closure-based versions into an
 extra module (that's easy enough with the hierarchical
 libraries).  This makes changing over old code easier, as it
 merely requires to alter the import and not all occurences
 of the functions.
 
 Any objections?

I have changed this in the spec now.  I attach the wording
used in the spec.

Manuel

-=-

\item[newForeignPtr ::\ Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)]
  Turn a plain memory reference into a foreign object by associating a
  finalizer with the reference.  The finalizer is represented by a pointer to
  an external function, which will be executed after the last reference to the
  foreign object is dropped.  On invocation, the finalizer receives a pointer
  to the associated foreign object as an argument.  Note that there is no
  guarantee on how soon the finalizer is executed after the last reference was
  dropped; this depends on the details of the Haskell storage manager. The
  only guarantee is that the finalizer runs before the program terminates.

  Whether a finaliser may call back into the Haskell system is system
  dependent.  Portable code may not rely on such call backs.
  
\item[addForeignPtrFinalizer ::\ ForeignPtr a - FunPtr (Ptr a - IO ()) - IO
  ()] Add another finalizer to the given foreign object. No guarantees are
  made on the order in which multiple finalizers for a single object are run.

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



Re: Cheap ForeignPtr allocation

2002-09-03 Thread Manuel M T Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

 I'd like to propose two new functions for the ForeignPtr interface:
 
   mallocForeignPtr  :: Storable a = IO (ForeignPtr a)
   mallocForeignPtrBytes :: Int - IO (ForeignPtr a)
 
 (the names can change, of course).  The implementations are trivial in
 terms of existing things:
 
 mallocForeignPtr = do
   p - malloc
   newForeignPtr p free
 
 mallocForeignPtrBytes size = do
   p - mallocBytes size
   newForeignPtr p free
 
 However, in GHC we can provide a far more efficient implementation by
 using pinned ByteArray#s, avoiding the overhead of malloc()/free() and
 the finalizer.  Since this is quite a common idiom when using
 ForeignPtrs, I think it's a good case to optimise.
 
 I did a little test, and using the above functions gave a 6x improvement
 in a small example which just repeatedly allocated a new ForeignPtr and
 passed it to a foreign function.
 
 The GHC implementation is to extend the ForeignPtr type like this:
 
   data ForeignPtr a 
 = ForeignPtr ForeignObj#
 | MallocPtr  (MutableByteArray# RealWorld)
 
 so it does in theory slow down normal ForeignPtrs slightly, but I didn't
 measure any difference in the limited tests I did.

I vaguely remeber that in the context of the withForeignPtr
discussion we where once trying to achieve some similar
effect (but couldn't come up with something that would
work).  Do you remember?  Does this, then, effectively solve
this old problem?  Wouldn't you want newXXX and withXXX
variants of the above, too?

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



Re: Library archives

2002-09-03 Thread Manuel M T Chakravarty

Simon Peyton-Jones [EMAIL PROTECTED] wrote,

 | .NET is a different beast from other calling conventions in 
 | that you may want to compile Haskell ccalls to .NET 
 | intermediate language.  In other words, it is about being 
 | able to implement ccall *on* .NET.  Thus, the mix.
 
 I think that is exactly the issue.  
 
 | At the moment, there doesn't seem to be much support for
 | [lib].  The last message from SimonPJ (a while ago) on this 
 | issues also seems to indicate that he isn't to bothered about 
 | it.  But AFAIK he is away at the moment.  
 
 So let's omit it for now; but we will need to think about what to 
 do when someone really does do a Haskell-on-.NET binding.

So, overall this point is settled, then; implying that we
stick with Alastair's recent change of the spec in that
regard.

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



Re: Proposed change to ForeignPtr

2002-08-12 Thread Manuel M T Chakravarty

We seem to have a consensus on this one.  We change the type
of the existing functions to

  newForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)
  addForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO ()

For GHC, I propose to put the closure-based versions into an
extra module (that's easy enough with the hierarchical
libraries).  This makes changing over old code easier, as it
merely requires to alter the import and not all occurences
of the functions.

Any objections?

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



Re: Library archives

2002-08-12 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

  Under .NET each DLL has its own namespace, so the [lib] spec is
  needed to disambiguate.  Since it's a namespace issue, I'd feel
  better if on .NET the name of the C function took a different form
  (perhaps lib.function) and [lib] is removed from the spec.
 
 Isn't that just a different syntax for the same thing?
 
 The thing I don't understand here is why .net issues affect the ccall
 calling convention and not the dotnet calling convention?
 
 I'm totally happy with defining dotnet to be ccall plus [lib] (or
 lib.) specifications (much as stdcall is defined as a small delta on
 ccall).  I know what that means and it is implementable on platforms
 which support dotnet.  It is trying to make C fit into the .net scheme
 of things which causes problems.

.NET is a different beast from other calling conventions in
that you may want to compile Haskell ccalls to .NET
intermediate language.  In other words, it is about being
able to implement ccall *on* .NET.  Thus, the mix.

At the moment, there doesn't seem to be much support for
[lib].  The last message from SimonPJ (a while ago) on this
issues also seems to indicate that he isn't to bothered
about it.  But AFAIK he is away at the moment.  

So, unless SPJ strongly objects when he returns, let's go
with Alastair's change.

Cheers,
Manuel

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



Re: Updates to FFI spec

2002-08-11 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

 For those not on the cvs mailing list:
 
 I've applied all the changes discussed over the last 2 moniths that
 received some support and no dissent.
   
   Changes since RC5:
   * Author list: changed Alastair Reid's institution
   * 4.1.1: Removed [lib] from impent syntax and discussion
[..]
   * 4.1.4: Removed all mention of library objects

Is SimonPJ ok with that?  We added [lib] for him (and .NET).

 You will need this file:
 
   http://www.cse.unsw.edu.au/~chak/haskell/grammar.sty
 
 to build it.  (I came close to adding this file to the repo but
 figured that Manuel must have a reason for not having done so
 himself.)

I wanted to change some stuff first and not track it in two
CVS repos.

 - I'd like to see a standard way to call the GC from C
 
 http://www.mail-archive.com/ffi@haskell.org/msg00565.html
   
   Note that Hugs and GHC have had this for ages except that we call the
   function 'performGC' and there's no way to control how many generations
   are collected.

I don't have a strong opinion on this one.

 - I see the question of Function prototypes as a portability problem
   waiting to happen.  Either Hugs and GHC are right (you should use the
   user-supplied header file or NHC is right (you should ignore the
   header file).  They can't both be right if we want portable code
   so the report should be clear about which one is right.
 
   (Given my druthers, I'd drop header files from the foreign import syntax
   and say that you have to specify it on the command line or propose that
   we standardize some variant of the GHCism {-# -include foo.h #-}.  But
   I'm not excited enough about it to push hard for this.)

I am still in favour of user-supplied header files and the
mechanism as it is defined in the spec right now.

 - Changes to hs_init 
 
 http://www.mail-archive.com/ffi@haskell.org/msg00539.html

I am ok with that.  Currently, there is a problem with the
version that is in the spec and GHC in that GHC requires an
extra argument to initialise modules.  So, it all depends a
bit on how far SimonM thinks its implementable.

Cheers,
Manuel

PS: Sorry for my prolonged procrastination over these issues
and thanks for picking them up.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Library archives

2002-08-11 Thread Manuel M T Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

  I see a lot of discussion about header files.
  I see a small amount of discussion of libraries with many conflicting
  suggestions.
  I see no _conclusion_.
 
 Ok, I can't see the conclusion either, but I seem to recall that at one
 stage the library specs were removed from the spec altogether and only
 came back again because of .NET 

Correct.

 (no, I'm not sure why they're in the C section of the FFI
 spec either).

Because they are for implementing calls to C code in Haskell
that is compiled to .NET ILX.

This doesn't mean that I want to necessarily defend them,
but this was the reason for their inclusion.  Essentially,
SimonPJ was saying that to compile Haskell including foreign
import ccalls to .NET ILX, we need the library spec.

I am not too fussed about .NET, so don't mind if we nuke the
[lib] specs (as Alastair already did in the CVS version of
the spec).

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



Re: Proposed change to ForeignPtr

2002-08-10 Thread Manuel M T Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

  What do you expect to happen if the finaliser calls a foreign
  exported function?
 
 Good question.
 
 I do not expect that to work on any platform that has difficulty
 implementing newForeignPtr (because you could use it to implement
 newForeignPtr).
 
 I don't know if it would be likely to work on GHC.

SimonM, what do you think?

 I think the spec should say that it is an error or undefined
 depending on whether GHC supports reentrant finalizers or not.

IMHO, it's a nice feature to have.  I understand that the
spec can't require it, as systems without preemptive threads
can't implement it.  However, it would be a pity if the new
interfaces would mean that even systems that feature
preemptive threads can't have it.

  That's a tricky one.  From the standards point of view, I am
  actually *very* reluctant to introduce new names.  On the other
  hand, reusing the old names will lead to a couple of unhappy emails
  from people using the old interface again.
 
 But only a couple I conjecture.

I read this as you would also (= like me) be in favour of
keeping the old names.  Right?

Other opinions?

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



Re: Generating Function Prototypes

2002-07-03 Thread Manuel M. T. Chakravarty

Alastair Reid [EMAIL PROTECTED] wrote,

  I've been having trouble with an imported function that returns
  Int64/long long. Haskell doesn't generate a prototype, so regular
  'int' type is assumed.
 
 Which compiler is this for?  As you saw from the other replies,
 compilers vary in whether or not they add prototypes.  GHC: yes, NHC:
 no, Hugs: depends which day you grabbed your copy from CVS.
 
 (I'm not sure that the ffi should allow compilers to vary in this way
 but it does.)

The FFI doesn't really allow compilers to emit prototypes
(at least not in general) as this leads to semantic
differences eg in argument promotion, for which Section
4.1.5 precisely specifies the behaviour.

And GHC doesn't emit prototypes.

If you have any suggestions as to how to make this point
clearer in the spec, please let me know.

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



Re: FFI Addendum, RC3 Open Issues

2002-04-23 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 Manuel M. T. Chakravarty wrote:
   [...] * 4.1.5: New section discussing the traps  pitfalls of type
   promotion with C bindings.
 
 The section in itself is OK, but it's a bit annoying IMHO that one can't
 write a portable foreign import for e.g. Unix' open, which has an optional
 mode parameter. I fear we have to reconsider varargs somehow...

The problem is that unless we require the Haskell compiler
to read header files, there is really know way it can know
which arguments are varargs.  So, I'd consider it something
that a higher-level tool may provide a more convenient
solution to, but with the basic FFI, you need to write a C
wrapper. 

   [...] * There is the open question, raised by SPJ, of whether we
 like to have something like
  
   import_entity - [String]
   export_entity - [String]
  
 See my message from yesterday.
 
 I would vote for the change, but could live with the current state of affairs.

As this is the only response re this point, I will effect
the change.

   [ new threadsafe mode ]
 
 Hmmm, I'm not so sure about this: Although it looks like something convenient,
 is there a real *need* for it or could the same be achieved by using additional
 (threading) library features? We should be aware of feature creep...

We knew that there will be an extra mode for threads all
along and Sigbjorn's proposal is simpler than the one that I
originally made.

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



Re: Freeing arrays

2002-04-08 Thread Manuel M. T. Chakravarty

George Russell [EMAIL PROTECTED] wrote,

 According to section 5.8 of the spec,  MarshalAlloc.free will free a block
 of memory that was allocated with malloc or mallocBytes.  Fine.  But will it
 also free blocks of memory allocated by MarshalArray.mallocArray and friends?

Yes, `mallocArray' is just a wrapper around `mallocBytes'.

 Come to think of it, what about MarshalArray.reallocBytes?

That can be free'd with `MarshalAlloc.free', too.

 Also, what is
 the realloc function mentioned in the specification of reallocArray, or do you
 mean reallocBytes?

Yes, `rallocBytes' is meant, but thinking about it, we might
actually add a function:

  realloc :: Storable b = Ptr a - IO (Ptr b)

I think, it is more orthogonal this way.  Any objections?

Cheers,
Manuel

PS: I'll make sure that these points are clarified in the
FFI spec.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI spec

2002-04-08 Thread Manuel M. T. Chakravarty

Simon Peyton-Jones [EMAIL PROTECTED] wrote,

 Since we have two productions, one for foreign import and one 
 for foreign export, let's separate the productions for entity into
 import_entity and export_entity.  That way we don't have to 
 say entity in *both* 4.1 and 4.2.  

Yes, I see your point.  On the other hand, we'd have

  import_entity - [String]
  export_entity - [String]

in the grammar in Section 3, then, and the introductory text
to Section 4 would have to always mention both
non-terminals.

Nevertheless, I think, I tend to applying this change.  Any
other opinions?

Cheers,
Manuel

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



FFI Addendum, RC3 Open Issues

2002-04-08 Thread Manuel M. T. Chakravarty

I have put Release Candidate 3 up at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

Changes wrt to the last version are the following:

* 3.2: Clarified the description of foreign types; so far, `IO ()' was
strictly speaking not included as a valid return type.
* 4.1.5: New section discussing the traps  pitfalls of type promotion with
C bindings.
* 5.8: Clarified documentation for `MarshalAlloc.free'.
* 5.8: Added `MarshalAlloc.realloc'.

Moreover, I would like to draw your attention to the
following points, which we should solve before I post the
next version to `[EMAIL PROTECTED]':

* Olaf Chitil has pointed out some unclear points wrt to ()
  and IO () as a result type in foreign declarations in the
  previous version of the Addendum.  I have edited Section
  3.2 to improve this, but you may want to check out that
  the new version meets your expectations.

* I have added Section 4.1.5 as a consequence of the recent
  discussion on argument type promotion on this list.  It
  seemed that everybody agreed what the FFI should do, but
  that a detailed explanation in the specification is
  needed, so I have added one.  Please check whether you
  find it sufficient.

* I think, for reasons of orthogonality `MarshalAlloc'
  should include

realloc :: Storable b = Ptr a - IO (Ptr b)

  I have added this in the document.  Let me know if anybody
  disagrees with this.

* There is the open question, raised by SPJ, of whether we
  like to have something like

import_entity - [String]
export_entity - [String]

  See my message from yesterday.

* Sigbjorn, while adding support for OS threads to GHC, has
  introduced a new safety mode `threadsafe'.  It seems
  worthwhile to include this into the Addendum.  On systems
  that don't support OS threads, `threadsafe' might behave
  like `safe', but at least code that uses `threadsafe'
  would still be valid on other systems.  The semantics is
  as follows:

   unsafe   must not call back
 
   safe may call back; if it blocks outside Haskell,
the whole Haskell system blocks
 
   threadsafe   on systems supporting OS threads, the
Haskell runtime will not block, even if the
call blocks;
must call an OS-thread safe procedure
 
  ('safe' remains the default.)

If there are no objections, I will add the latter two
changes to the FFI Addendum.

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



Re: [HOpenGL] Re: FFI Addendum, CVS Id 1.19

2002-01-10 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 The addendum looks fine for me, well done Manuel! But as usual, I've got a few
 minor points:
 
* Section 3.4 (export declarations) says:
 
 If an evaluation triggered by an external invocation of an exported
  Haskell value returns with an exception, the system behaviour is
  undefined.
 
  So far, so good... It continues:
 
 Thus, Haskell exceptions have to be caught within Haskell and
  explicitly marshalled to the foreign code.
 
  I understand the idea here, but what about System.exitWith and
  System.exitFailure in callbacks? GHC implements this via throwing an
  exception, but this is an implementation detail IMHO. The consequence
  of this implementation choice is a fatal error (uncaught exception)
  when exit{With,Failure} is evaluated in callbacks. So there are two
  questions:
 
 * Should we allow exit{With,Failure} in such circumstances?
   (My opinion: yes)
 
 * If the answer is no, what is the official way to terminate
   cleanly from callbacks? Note that in the context of HOpenGL
   the callback can't return a value due to the nature of an
   external lib (GLUT). I fear that the answer could be hs_exit(),
   but that would lead to a backwards compatibility hell...

I really think that this is GHC's problem.  What the FFI
report says is that the *user* cannot expect to get an
exception properly marshalled across a callback.  If GHC
uses exceptions internally to implement features, which H98
doesn't define to be based on exceptions, then it is GHC's
responsibility to handle these special exceptions in a
special way.  Overall, I guess, GHC needs to check - at
least - for exit{With,Failure} failures at callback
boundaries and handle them appropriately.

* The example in section 5.4.2 should use wrapper instead of the old f.e.d.

Oops.

Cheers,
Manuel

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



FFI Addendum 1.0, Release Candidate 1

2002-01-10 Thread Manuel M. T. Chakravarty

Folks,

To bring the definition of FFI 1.0 to an end, I have
incorporated the comments from the last round (changes are
listed below) and set up a proper web page, which includes
Release Candidate 1 of the standard:

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

If I don't hear any loud screams until tomorrow (southern
hemisphere Friday morning), I'll post this to
[EMAIL PROTECTED] for general discussion and will ask
for inclusion on http://haskell.org/.

From now on, we are in pure bug fix mode.

Cheers,
Manuel

-=-

Changes:
* infix declarations for shift[LR] and rotate[LR] in Bits
* Corrected `mkCompare' example in Section 5.4.2
* Fixed the type of `mkCallback' in Section 4.1.3
* Added acknowledgments

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



Re: FFI Report comments

2001-08-30 Thread Manuel M. T. Chakravarty

[I'll just respond to a couple of points, the rest I have
silently accepted or put on the todo list, or it will be
discussed in a later message.  This includes Malcolm's first
email, too.]

Malcolm Wallace [EMAIL PROTECTED] wrote,

 Lexical Structure
 ~
 The lexical syntax adds 'foreign' as a keyword (reservedid).  I'm not
 entirely convinced this is necessary.  Certainly in nhc98 we treat
 'foreign' as just a specialid, and so like with other specialids you
 can name a variable 'foreign' if you wish.  In other words, is there
 any real reason to exclude the possibility of
 
 module F (foreign, as) where
 
 foreign :: X - Y
 foreign ... = ...
 
 foreign import ccall something as :: CInt - CInt - CInt
 
 which nhc98 currently accepts, but ghc -fglasgow-exts rejects?

As I understand H98's distinction between reservedids and
specialids, any id that introduces a new grammatical phrase
is a reservedid.  Otherwise, why is `data' not a specialid?

So, I believe it is more inline with H98 to make `foreign' a
reservedid.

 Standard C Calls
 
 The productions
 
 fdecl  - 'import' callconv [safety] entity var '::' ftype
 entity -  ['static'] [fname] [''] ['['lib']'] [cid] 
 
 suggest that the entity string must always be present, but could be
 .  I was wondering if there is any real difficulty in permitting
 an empty entity string to be omitted altogether?  The idea would be
 to be able to write
 
 foreign import ccall sin :: CFloat - CFloat
 
 as at present rather than
 
 foreign import ccall  sin :: CFloat - CFloat
 
 It isn't a big deal, and it might be worth enforcing the literal string
 quotes just for uniformity, but I thought I'd raise the issue anyway.

Then, we also have to define

  entity - [string]

at the start of Section 3.  I actually considered this, but
just went for the simpler syntax.  But I would also be happy
to allow omitting the .

 Int and Word
 
 You want to drop the assertion that arithmetic is performed
 modulo 2^n for sized Int and Word types, on the grounds that this
 doesn't hold for Int.  But Int is not of fixed size, so how could it
 require modulo arithmetic!  I happen to think the fact that Int is of
 unspecified size 30 bits, with undefined behaviour on overflow, was
 something of a mistake in Haskell.  Now that we have the opportunity
 to define a sensible overflow behaviour for fixed size types, I think
 we should take it.

Ok - the general opinion here seems clear.

 module StablePtr
 
 It seems a little strange that there is an instance of Storable
 for StablePtr, yet we are forbidden to use the methods of Storable
 to dereference a StablePtr.  In other words, I'm not quite clear on
 exactly what is being forbidden.

The Storable instance allows to store `StablePtr's
themselves (ie, the value that represents them) rather than
then the value that they refer to - the latter may not be
accesses using Storable.

Cheers,
Manuel

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



Re: FFI Report comments

2001-08-23 Thread Manuel M. T. Chakravarty

Malcolm Wallace [EMAIL PROTECTED] wrote,

 Typos
 ~
 There are a few typos and mis-spellings.  Would it be easiest for
 someone like me to fix these directly via CVS, or is it better to
 just give you a list privately?  I must admit that my experience of
 using CVS for LaTeX documents was not a happy one, compared to how
 useful it is for source code.

Especially with respect to small changes, I think, it is
fine to do them directly via CVS.  However, to be one the
safe side, I propose to always do a cvs update before
changing anything and to commit the changes at fairly small
intervals.  Given that this is LaTeX and we don't have to
worry about breaking a build, this shouldn't be a problem.

However, if anybody prefers emailing me the corrections for
me to enter, I am happy to do so.

Manuel

PS: More re the technical comments later.

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



FFI Report, CVS Id 1.11

2001-08-19 Thread Manuel M. T. Chakravarty

Folks,

After another teaching-enforced pause, I have continued
working at the FFI Report:

  http://www.cse.unsw.edu.au/~chak/haskell/ffi.ps.gz

For C, the report should now be essentially complete (I have
included all the libraries).  There are, however, still some
outstanding issues (see the report and below for the gory
details).  For all calling conventions other than ccall and
stdcall, most is still missing.

My plan for driving this further is as follows:

* Get all but the most controversial outstanding issues for
  the language-independent and the C binding fixed until
  ICFP.

* Have a meeting at ICFP to nail any remaining issues in the
  language-independent and C binding as well as discuss how
  much we exactly want to do for other calling conventions
  and how we go about doing it.

Could everybody who is coming to ICFP and would like to
attend the meeting drop me a note please?  Just so that we
can fix when to meet.  I will be in Florence from Saturday
around noon until the following Friday (maybe even Saturday)
noon.

Cheers,
Manuel

PS: The source of the document is in cvs.haskell.org and at 
http://www.cse.unsw.edu.au/~chak/haskell/ffi.tex.

-=- The Gory Details(TM) -=-

I went through all messages on this list that I hadn't
responded to yet and either included the suggestions or they
are discussed below.

static keyword

Marcin wrote re removing the static keyword in C extents,

 What the lack of static takes away is the ability to import a function
 called dynamic or wrapper. I don't think that it's a big limitation
 considering hundreds of names which are taken away by a Haskell's
 runtime system.

IHMO, it is one thing for an implementation to do that and
another for a language definition.

 Anyway, we could call them _dynamic and _wrapper to indicate
 that they are magical in some sense - using such names for external
 function names would be a violation of ISO/ANSI C rules (they are
 reserved for the C implementation).

*urgh*  I think, that's uglier than having static.  So,
I'll stick with static unless there are serious counter
arguments. 

Backward compatibility
~~
Malcolm raised the issue of backward compatibility.  As I
understand it we aren't concerned about the definition
actually encompassing the syntax and semantics currently
implemented in GHC and NHC, but there is an understanding
that those system will allow the old syntax for a while
after they adopt the standard.

NHC's current implementation of foreign export  

From the discussion, it seems that NHC simply allows the
phrase foreign export in front of the normal type
signature of a function (as opposed to in addition to that
type signature).  I never had this in mind and it has always
been different in GHC and in Sigbjorn's FFI spec.  In fact,
being able to have

  foo :: Num a = a - a
  foo  = ...

  foreign export foo :: Int - Int

was always sold as a feature of the system.

Further additions to the FFI

IMHO, the FFI should really be self-contained and not rely
on other non-standardised extensions/libraries.  Therefore,
I propose some additions.

* I think, we should include the `Bits' module (or something
  similar).  It is needed, eg, to handle bindings to C
  functions that expect bit vectors as arguments.  

* To implement marshalling for foreign imported pure
  functions, `unsafePerformIO' is essential.  We could add
  it to the module `Foreign' or `MarshalUtils'.  This raises
  the question of whether `unsafeInterleaveIO' falls in the
  same category.  I think, we should add `unsafePerformIO'
  and leave `unsafeInterleaveIO' our as it is less important
  for the FFI.

* Why do we only have `Eq' on ForeignPtr, but also `Ord' and
  `Show' on Ptr?  I'll add `Ord' and `Show' to `ForeignPtr'
  unless their are objections.

* Should HsFFI.h include a function like GHC's
  startupHaskell()?  For linking Haskell libraries into
  foreign code that seems to be necessary.  So, I vote for
  inclusion. 

Superflous stuff

* I am still not convinced that we need
  `Storable.destruct'.  For deallocating special purpose
  structures that need a deep traversal, shouldn't we just
  use a custom function?

* I am also not really convinced about
  `MarshalUtils.withMany'.  There may be situations, where
  such a function is handy, but should it really be in the
  standard libraries?  Moreover, it isn't really marshalling
  specific - it is JAFL (Just Another Function on Lists).

Names
~
* I don't think `CTypesISO' is a good name.  Maybe
  `CTypesLib' as it contains the types from the C library
  (as opposed to the normal builtin types)?  Or put it all
  into `CTypes' after all - that doesn't mean GHC (or any
  other compiler) has to put it into a single module, just
  for the definition.  I tend to having one module only.

PtrDiff
~~~
Maybe after all, `PtrDiff' wasn't that bad an idea.  To

Re: FFI Report, CVS Id 1.5

2001-06-17 Thread Manuel M. T. Chakravarty

Fergus Henderson [EMAIL PROTECTED] wrote,

 On 15-Jun-2001, Simon Peyton-Jones [EMAIL PROTECTED] wrote:
  I'm trying to compile Haskell for the .NET platform.
  For this platform it makes perfect sense to say
  
  foreign import ccall  foo foo :: Int - Int
  
  because you can make C calls on .NET as well as .NET calls.
  The problem is that the call must specify which DLL the 
  function comes from.  The line in the .NET assembly code
  looks something like
  
  pinvoke dllname::foo 
 
  I remember now that this is why I originally suggested that
  the C calling convention specify a package name rather
  than a header file name. Thus
  
  foreign import ccall wuggle::foo foo :: Int - Int
  
  rather than wuggle.h
 
 The main problem with that is that in general there will not be
 any relationship between the DLL name and the header name.

In particular, this encourages non-portable code.  Assume, I
develop a Haskell-to-C binding for a library whose header
file is called `myheader.h' and whose dll is `mylib.dll'.
Now, when I develop this binding in a fully statically
compiled environment, I might use

foreign import ccall myheader::foo foo :: Int - Int

and make sure that the right library `mylib.dll' is linked
against in the command line options to the compiler.

Now, if I run the same code on .NET, it breaks as it
attempts to load `foo' from `myheader.dll'.

Simon Peyton-Jones [EMAIL PROTECTED] wrote,

 I'm conscious that this is resurrecting old territory; if it's been
 done to death already, just say 'no'.
 
 I suppose in that case I will have to add an extra .NET form
 
   foreign import dotnet callC wuggle::foo foo :: Int- Int

IMHO, this is not a very attractive solution.  I'd prefer to
complicate the ccall entity description slightly and go for

foreign import ccall myheader.h foo@mylib foo :: Int - Int

Ie, we optionally allow the specification of the name of a
dll.  This is only a hint and may be ignored by a given
Haskell system (in particular, in most systems, command line
options overrule such library names).

Any objections?

Cheers,
Manuel

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



FFI Report, CVS Id 1.5

2001-06-09 Thread Manuel M. T. Chakravarty

There is now a new revision of the definition at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}

Simon Peyton-Jones [EMAIL PROTECTED] wrote,

 Suggestion: would you like to add this to the CVS repository.
 Then others can get hold of it, and even modify it (e.g. correct
 typos, add examples).  It's inefficient to type a message saying
 add a comma after ..bubble...
 
 There's an obvious place for it.  The Haskell Report is in the
 CVS repository cvs.haskell.org in the 'module' haskell-report.
 Thus
   cvs checkout haskell-report
 
 There is a sub-directory for report/ and another for libraries/,
 so you could just create a directory for ffi/.

Done.  The .tex and .bib files are in this directory.  For
formatting the file, my grammar.sty is missing.  I will soon
put this in there, too.

However, concurrent editing of text files is much more
dangerous conflictwise than program code.  So, please always
update the local copy before changing it and check in
changes immediately to avoid problems.  Moreover, I think,
any changes concerning the semantics of the document should
still go through me.

 *  I strongly suggest however adding a brief collection of examples 
 as Section 1.3  (or Section 2).

Examples before the definitions?  Won't they be more
meaningful later on?

 * Similarly, for each language-specific section, we must add a
 collection of examples.
 No one who was not intimately familiar with the FFI would
 be able to make sense of 'import dynamic' or 'import wrapper'.  

Yes, I added a few now, but I am aware that these are still
not sufficient.  More to come...

 * You mention en passant that there's a new type CInt.  Very good, but 
 the full set of types (and their operations) must be defined in the 
 language-specific sections.  Indeed, I suggest we take 3.2 and 
 make it a top-level Section, with a sub-section for each language.

The types have to be defined, but I was planing to do that
as part of the libraries (where they are defined).  One
reason for that is that with calling conventions like
dotnet, the correlation between calling convention and
language (and so language-specific types) becomes unclear.

 * external types are mentioned in 3.2.1 but nowhere defined.

 * Nowhere do you say that in 
   foreign import ... foo :: type
   that this defines the Haskell variable 'foo' with type 'type'.
 (Currently
   it's just defines a variable, with nothing about type.)

I have filled in the sections detailing import and export
declarations and foreign types now.

 * I think we are agreed that the stuff about marshalling libraries
 belongs in
 this document too.  Much of it is already written.  Could it be
 incorporated?

Yes.  However, as the libraries are the most stable part of
the whole FFI story at the moment and incorporating the
exiting descriptions is largely an exercise in type setting,
I was leaving this until the rest has settled.

Foreign Types
~
This looks quite different from the old FFI spec.  Problems
with old specification:

* It doesn't make much sense to name data constructors in
  the grammar (we don't know from which module they are) and
  the grammar didn't consider qualified identifiers.

* Doesn't take the reversed data flow between foreign import
  and export into account (important for where `ForeignPtr's
  can appear).

* The treatment of newtypes was rather ad hoc.

The new definition reduces the problem of defining exactly
which types can be marshalled to a reference to Storable.
IMHO this is more elegant and more rigorous.  However, there
is one caveat to cleanly defining it, newtypes that need to
make use of the newtype transparency during marshalling
have to include a `deriving Storable' in their definition.

Consequently, Storable must be derivable.  This, I believe,
is a reasonable extensions as the Haskell 98 report says in
Section~4.3.3, ``Classes defined by the standard libraries
may also be derivable.''  The restriction would be that only
newtypes of instances of Storable can derive Storable.

Open questions
~~

* Consider

foreign import foo foo :: t

  Currently, it can also be written in the following forms:

foreign import static foo foo :: t
foreign import static foo :: t
foreign importfoo :: t

  Is the last one nice?  Shall we make the external entity
  optional as in

foreign import  foo :: t

  and make it default to .  (The same issue arise for
  foreign export, of course.)

* How feasible is it not to allow exceptions to be
  propagated from an external entity to Haskell land in case
  of JNI?

* The old FFI spec restricted `ft' to `prim_args - IO
  prim_result'.  Why didn't forbid thunks and pure
  functions?  Is this really necessary?

* How many calling conventions should we nail down now?
  What should we say about the others (in particular
  cplusplus)?

Note


I have added a restriction: exported variables must be
defined by a function or pattern 

Re: FFI Report, CVS Id 1.4

2001-06-02 Thread Manuel M. T. Chakravarty

Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote,

 Fri, 01 Jun 2001 18:36:01 +1000, Manuel M. T. Chakravarty [EMAIL PROTECTED] 
pisze:
 
http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}
 
 I like it. 

Fine :-)

 Minor issues:
 - import is not a specialid, it's already a reservedid.
 - Safeness should be optional. (And maybe s/safeness/safety/ ?)

Ok, I changed all that.

 - Would anyone really use explicit static?

Yes, because when you want to import the C identifier
`dynamic' or `wrapper' and not provide a header file.
Moreover, I think, it is more orthogonal.

Cheers,
Manuel

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



FFI Report, CVS Id 1.4

2001-06-01 Thread Manuel M. T. Chakravarty

...is available at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}

It contains the results of the discussion on external
entities for the C calling conventions.

Summary of changes:

* Modifiers are at the moment only for import declarations.

* import = define variable; export = use variable

* Import declarations in ccall have the following form

  entity -  ['static'] [fname] [''] [cid] 
 |   'dynamic' 
 |   'wrapper' 

  where `fname' is the name of a header file that must end
  in `.h'.  If `' prefixes the cid, we import the address
  of that label.  `dynamic' corresponds to the old import
  dynamic and `wrapper' to the old export dynamic.  This has
  essentially the same functionality as Sven's last posting,
  but allows to specify a header file without being forced
  to specify the C identifier.

* Appendix B contains a rationale for items about which
  there has been much discussion.

Open question:

  In foreign import dynamic, the old FFI spec restricted
  type of dynamically imported functions to 

prim_args - IO prim_result  

  Why did it forbid thunks and pure functions?  Is this
  really necessary?

Cheers,
Manuel

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



Re: Again: FFI syntax

2001-05-31 Thread Manuel M. T. Chakravarty

Michael Weber [EMAIL PROTECTED] wrote,

 On Wed, May 30, 2001 at 22:59:37 +1000, Manuel M. T. Chakravarty wrote:
  So, it all boils down to the question of whether this
  (probably rare) case justifies the (not very large) extra
  complexity of allowing header file names enclosed in .
  
  I am happy either way, but slightly tend to the simpler
  solution (not allowing ).  Would everybody who prefers to
  have  please say so and briefly say why?
 
 Sorry for dropping into the discussion, but...

You are always welcome, Michael :-)

 Using  instead of  once caused me some problems (can't recall what
 it was in particular).  However, since then my standard was to always
 use  and handle the  case by adding -I. parameters...  That would
 also have the benefit of being somewhat less dependant on the
 behaviour of a implementation (as somebody quoted from the standard).
 If you put -I. in front, it will always get searched before include dirs 
 given by subsequent -I options, right?

This is not guaranteed by the standard.  The ISO C99
standard (as quoted by Fergus earlier) says for 

  [..] searches a sequence of implementation-defined places
  [..] How the places are specified [..] is
  implementation-defined.

However, the standard does guarantees for  that 

 The named source file is searched  for  in an
 implementation-defined manner.   If [..] the  search
 fails,  the directive is reprocessed as if it read

# include h-char-sequence new-line

So, it seems that using  is more portable than using  in
conjunction with -I.

I will leave it with  as the only option, then.

Cheers,
Manuel

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



Re: Again: FFI syntax

2001-05-31 Thread Manuel M. T. Chakravarty

Fergus Henderson [EMAIL PROTECTED] wrote,

 On 31-May-2001, Manuel M. T. Chakravarty [EMAIL PROTECTED] wrote:
  Fergus Henderson [EMAIL PROTECTED] wrote,
   Making the semantics of a particular construct implementation-dependent is
   a good thing if the semantics that you want are implementation-dependent.
   Doing this allows the code to work correctly on different implementations
   without modifying the code.
   
   That is the case here, I believe.  In particular, ccall is not abstract
   enough to use as a default.  The default calling convention -- the one that
   you normally want -- is whatever the corresponding C implementation uses.
   But on x86, ccall means a *particular* calling convention (args passed
   on stack, caller pops, return value in EAX, etc.) which may not match
   the one that your C implementation uses.  If you have a C implementation
   which always passes args in registers, as is certainly allowed by the C
   standard, then you want to the default calling convention to be passing
   args in registers, otherwise nothing that uses the default will work.
  
  How about saying that `ccall' means whatever the
  corresponding C implementation uses on any platform?
 
 I would be fine to say that some other name, e.g. `c', means that.
 But `ccall' already has an existing meaning, and it would be
 terribly confusing if e.g. MSVC and GNU C used `ccall' to mean one thing,
 while Haskell used it to mean something different.

Are you sure that ccall has a fixed meaning outside of the
Haskell community?  A google search for `ccall' comes (wrt
to programming languages) mainly up with Haskell references.

If `ccall' is really fixed, then I would prefer to introduce
a new calling convention (eg, `c') rather than using an
unspecified calling convention.

Cheers,
Manuel

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



Re: FFI Definition

2001-05-29 Thread Manuel M. T. Chakravarty

[Sorry for being absent from this discussion for a while.
Teaching took its share...]

Sven Panne [EMAIL PROTECTED] wrote,

 Simon Marlow wrote:
 
  The reason for not putting them in the source is because the names of
  libraries change from system to system but their APIs don't.  It's
  possible to write a portable binding to an API if you don't have to
  include the libraries,  but including the library names requires
  information from the system, which is normally picked up by a configure
  script. [...]
 
 I'd go even one step further: Often even the names of #include files
 differ for the same API, or you have to #include some other headers
 first, etc., just take a look into GHC's RTS for example. If we specify
 #includes in the FFI, we effectively resort to autoconf or something
 like that in our hand-made #include files most of the time, I fear.
 (or clutter up the Haskell sources with #if #endif :-P ) But most
 people on this list think different and you don't have to use this
 feature, so I can live with that.

For .h files, you can always define your own .h file, which
includes everything in a system-dependent manner.  For
libraries that have to be linked in, a similar mechanism is
not feasible.  Therefore, it is reasonable to handle `.h's
and libs differently.

Cheers,
Manuel

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



Re: Again: FFI syntax

2001-05-29 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 Fergus Henderson wrote:
 
  The calling convention should not necessarily default to 'ccall'.
  That would not be appropriate for all implementations.
 
 Granted.
 
  Instead, I think the default calling convention should be
  implementation-dependent.
 
 Hmmm, this would make the semantics of the sources compiler-/interpreter-
 dependent, which is never a good thing. 

That's what I think, too.  In addition, I can't see that it
would buy us anything.

 So let's simply make callconv
 mandatory, ccall isn't that long after all.

If this is generally preferred, ok.  (I won't change it, though,
unless I hear more people asking for it.)

  Also, implementations should be allowed to provide calling conventions
  not on that list.
 
 IIRC the intention for enumerating some calling conventions here is to
 make future implementations agree on the name of callconv when they
 implement e.g. a C++ or Java FFI, not to rule out other possibilities.

Exactly.

 But this should be made clear from the FFI spec.

The spec said,

  Generally, the set of calling conventions is open, as it
  is infeasible to cover all useful calling conventions in
  this report.

I have changed this now to

  Generally, the set of calling conventions is open, i.e.,
  individual implementations may elect to support additional
  calling conventions.

Alternative wordings are welcome.

Manuel

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



Re: Again: FFI syntax

2001-05-29 Thread Manuel M. T. Chakravarty

Fergus Henderson [EMAIL PROTECTED] wrote,

 On 29-May-2001, Sven Panne [EMAIL PROTECTED] wrote:
  I'm against *always* wrapping the header file name
  in double quotes, unless
  
 #include foo/bar.h
  
  implies
  
 #include foo/bar.h
  
  if the first form is not found.
 
 It does.
 
  I'm not sure about this, although it's guaranteed
  the other way round IIRC.
 
 You recall incorrectly.
 
 For ..., the search is entirely implementation-defined [ISO C99 6.10.2#2].
 For ..., the initial search is implementation-defined, but it if fails,
 then the search is retried as if for ... [ISO C99 6.10.2#3]:

Oh, great - I should have read this message before replying
to Sven's.  Then, this issue should be settled.

Thanks,
Manuel

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



RE: Revised FFI syntax + typing

2001-05-06 Thread Manuel M. T. Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

   Why is Word a GHC extension?  Someone remind me?
  
  Hmmm, I thought that the Word type itself is a GHC extension, the
  hslibs docs for module Word only talk about the explictly sized
  variants. OTOH the implementation exports Word, but for legacy
  reasons, IIRC. If this is really the case, we should document this
  somehow in the sources.
 
 I don't think I have any strong feelings either way.  Word has a
 pleasing symmetry with Int, but on the other hand if it isn't useful
 then we should omit it.  I agree in principle with Alastair's
 portability argument, but don't think it is worth applying for this
 particular case since we already have Int.

I mostly agree with Simon.  There is no point in trying to
fix a problem that H98 already introduced.  The H98
Committee in their infinite wisdom chose to have types with
system-dependent sizes and I think, we should be as
orthogonal as possible whether we like it or not.

Moreover,

 In the absence of a Bits Int instance I would have to write the code
 like this:
 
 -- this code to go in the same file as the code that assumes that
 -- Int and Int32 are isomorphic
 #if sizeof_Int == 32
 type Intlike = Int32
 toIntlike = intToInt32  -- or fromIntegral
 fromIntlike = int32ToInt
 #elif sizeof_Int == 64
 type Intlike = Int64
 toIntlike = ...
 fromIntlike = ...
 #else
 #warning ...
 #endif

Interesting language, but can anyone remind me what these
#if etc are supposed to me - I can't find them in the
Haskell report.

Cheers,
Manuel

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



Re: Revised FFI syntax + typing

2001-05-06 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 Simon Marlow wrote:
  A totally minor point, but 'wincall' doesn't feel right. [...]
  I'd stick with 'stdcall' because that's what everyone else seems to call
  it.  gcc has a 'stdcall' function attribute, BTW.
 
 OK, so let's forget about 'wincall' and continue using 'stdcall'.
 Inventing new names for things already in existence is not a very
 good plan.

As I seem to be the only one who is really against stdcall,
let's revert to it *sigh*

Manuel

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



Re: FFI Definition

2001-05-06 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 Manuel M. T. Chakravarty wrote:
  [loading dynamic libs problem]
  This is just like the library object specification that we have now also.
 
 Huh? What? I've never seen a lib object spec... (or completely forgot it %-)

Like so

  foreign import ccall libgtk.so gtk_widget_destroy
gtk_widget_destroy :: Addr - IO ()

  [static/dynamic + callconv]
  Meanwhile, I think, you are right, we cannot make a clean
  language-independent static/dynamic distinction.
 
 The callconv already prescribes the syntax of ext_ent and the typing, so
 it could prescribe the possibilities for mode, too. And static/dynamic
 makes sense e.g. for cplusplus and jvm at least, with a slight
 reinterpretation of the actual meaning, but that's not very crucial.
 
 I'm against stuffing everything into ext_ent in a string form, which would
 mean a mini-language within Haskell (TCL is lurking! :-). My proposal:
 
-- allowed for import/export
mode : 'static'-- allowed for ccall/stdcall/cplusplus/jvm/..., default 
then
 | 'dynamic'   -- allowed for ccall/stdcall/cplusplus/jvm/...
 | 'interface' -- allowed for jvm
 | ...

The current idea is to make the syntax of the FFI extension
independent of the supported languages.  This requires to
stuff everything into `extent'.  Sure, this will make the
`extent' string complex for some languages, but that's
inevitable for anything but C anyway.  The old design really
benefitted from that we basically considered C only.  The
goal now is to bring the whole thing into better shape for
supporting multiple languages and being open for addition of
new calling conventions later.

 And for legacy reasons we have to keep dynamic for some time, anyway.

Let's forget about the legacy stuff for the FFI definition.
The systems have to support the legacy syntax, but that's
really of no concern for the definition.

   Also should 'label' be there?  Doesn't make sense for Java, does it?
  
  Hmm, not really.  So, also into `extent'...
 
 But it *makes* sense for some calling conventions, and it the actual
 translation will need the callconv (name mangling!), so the only change
 I propose here is a comment:
 
fkind: 'import'
 | 'export'
 | 'label'-- allowed for stdcall/ccall/cplusplus
 
 Hmmm, looking at the whole foreign beast gives me a slightly uneasy
 feeling now. There are loads of strongly interconnected side conditions,
 but I fear we can't avoid this because of the complexity of the whole
 topic. But at least we should strive for an ext_ent with minimum complexity
 when we go the special id way, like we did in the past.

The other design, which I believe is cleaner (and which I
understand as the consensus at the HIM meeting), is to get
rid of all the side conditions and put all the calling
convention dependent stuff into `extent'.  The latter is
calling convention dependent and complicated (for everything
but C) anyway.  So, let's at least keep the rest simple.

In fact, any system supporting a calling convention like
jvm, will have to have a parser for extent strings anyway.

 Another extreme route would be:
 
topdecl  : 'foreign' string var '::' type
 
 with a separate syntax for the string contents. 

Yes that's going into the right direction, but it makes
sense to leave both the calling convention as well as
import/export out of the string.  The calling convention
defines which parser to use in the string.  That's good for
implementers, because then, the parser can be chosen before
parsing starts.  The import/export information is needed by
the name analysis, which we better leave independent of the
whole extent mess.

In other words, having the calling convention and
import/export seperate facilitates more modular compiler
support. 

Cheers,
Manuel

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



Re: FFI Definition

2001-05-06 Thread Manuel M. T. Chakravarty

There is now an updated version of the document at

  http://www.cse.unsw.edu.au/~chak/haskell/{ffi.ps.gz,ffi.tex}

The LaTeX file is to make citing from the document easier
(as suggested by Fergus).  To compile it, you need a style
file which I first have to polish a little more before I put
it on the net (will all happen in due course).

The new version includes the feedback so far.  The main
change is that label, static, and dynamic are now part of
`extent' for `ccall' and `stdcall'.  It still has many gaps,
but I think it is important to regularly post updates even
if the delta is not very big.

Cheers,
Manuel

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



Re: FFI Definition

2001-05-03 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] wrote,

 This document looks like a very good starting point.
 
   * An omission: 'foreign label'.

Oops.

   * Perhaps the 'specialid' production should contain all the calling
 convention identifiers?

Yes, I had a weird idea here, but realise now that it
doesn't work anyway.

[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote,

 Your syntax puts modifiers between the calling convention and the
 external id. I agree that it's consistent. Currently ghc accepts
 unsafe only between the external id and the Haskell id, and dynamic
 only instead the external id.

Yes, the idea was that this has to be changed in GHC.

Sven Panne [EMAIL PROTECTED] wrote,

  * Because of the reason stated above, I think static/dynamic  *must*
come first after import/export, but the order of unsafe/safe,
callconv, and extent should not matter. The var (*not* varid, it was
a design flaw IMHO)

I agree.

  must be the last thing before the colon,
otherwise it tends to drown in the syntax. 

Yes.

  * I don't understand the last part of section 3.2.1, mentioning the
loading of dynamically loaded libs. Is something like dlopen() meant
here or linking against a libfoo.so? And the details of how/when this
linking should be done are completely obscure to me.

This is just like the library object specification that we
have now also.

Simon Peyton-Jones [EMAIL PROTECTED] wrote,

 |  language specific stuff inside the ... string
 |  language independent stuff outside
 | 
 | But static/dynamic probably means different things, depending 
 | on the callconv.
 
 I think it's arguable that static/dynamic should be inside the ext_ent
 string.  Indeed, one might use static/dynamic for ccall, and
 virtual/non-virtual/static for Java, etc.  Baking in static/dynamic
 for all languages may be inappropriate.
 
 Nevertheless, you propose keeping 'mode' outside the ext_ent string.
 Why?  (Apart from backward compat.)

Meanwhile, I think, you are right, we cannot make a clean
language-independent static/dynamic distinction.

 Also should 'label' be there?  Doesn't make sense for Java, does it?

Hmm, not really.  So, also into `extent'...

Simon Marlow [EMAIL PROTECTED] wrote,

 A totally minor point, but 'wincall' doesn't feel right.  This
 alternative calling convention has been around since long before windows
 (it's always been the default calling convention for Pascal, I think).
 
 I'd stick with 'stdcall' because that's what everyone else seems to call
 it.  gcc has a 'stdcall' function attribute, BTW.

Ok - so who prefers `stdcall' and who something else.

BTW, I have only included C++ for the sake of completeness
into the calling conventions.  As nobody is actively working
on this - or is there? - I am quite happy to not define
anything about it, but the name of the calling convention.
Better no definition than an untested one.

Cheers,
Manuel

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



FFI Definition

2001-04-17 Thread Manuel M. T. Chakravarty

Folks,

As promised, I have started on a definition of the Haskell
FFI.  I started by formalising those aspects of foreign
exports and imports that we have recently discussed here.
You can access the current text at

  http://www.cse.unsw.edu.au/~chak/haskell/ffi.ps.gz

In addition to general comments, I would particularly
welcome your opinion on the FIXME issues.

You may note that I have tilted the specification of the
calling convention and the related string determining the
external entity very much into the direction of the
execution platform.  In my opinion that makes the whole
description much more consistent.  In particular, we are now
talking about JVM calls rather than Java calls.  This fits
much better with ccall, wincall, and dotnet.  It also makes
it much more natural to talk about calling conventions
rather than programming languages implemented in terms of
these calling conventions.

I will add more material (including also a specification of
the FFI library) as we go.

Cheers,
Manuel

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



RE: FFI progress

2001-04-16 Thread Manuel M. T. Chakravarty

"Simon Peyton-Jones" [EMAIL PROTECTED] wrote,

 Manuel
 
 | The FFI discussion seems to be completely stalled.  Would 
 | you, as our Tsar, like to summarise the state of play, and 
 | re-invigorate it? 
 
 There was a bit of discussion, which led, I think to a simplification
 of the library stuff.  But we don't have a summary (even informal)
 of the current state of play, and that's beginning to be a problem here
 because we're about to implement the .NET FFI for GHC.

I am at this now.  Starting with the foreign import/export
declarations to summarise what we discussed.

 There's one particular issue we havn't discussed.  For Java and .NET
 we want to call static methods, dynamic methods, and constructors.
 We already have
   foreign import static
   foreign import dynamic
 
 but 'new' is different again.  The obvious place for it is in the
 language-specific
 string
   foreign import static "new foo(int x)" foo :: Int - IO Foo
 
 It seems a bit odd to have static/dynamic *outside* but "new" inside the
 language-specific string.  I suppose the justification is that 'new' is
 really
 a static method with a funny way to call it.   Whereas the 'self'
 parameter
 on a dynamic call is treated specially.

Basically, as you say, from the point of Haskell, `new'
really is not that special, but there is a huge difference
between `static' and `dynamic'.  I think, this justifies
pushing `new' into the language specific string.

Cheers,
Manuel

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



RE: FFI progress

2001-04-11 Thread Manuel M. T. Chakravarty

"Simon Peyton-Jones" [EMAIL PROTECTED] wrote,

 | In case you aren't aware of this, Windows DLL's by default, (actually
 | always, as far as I know) use the stdcall (Pascal) calling convention.
 | 
 | I personally hope that you won't drop anything which facilitates using
 | Haskell under Windows.
 
 Dead right.  I wasn't proposing removing the functionality, just
 changing
 how to get at it.  More concretely, there are two alternatives
 
 1.  Treat C-via-stdcall and C-via-ccall as two different "languages".
   E.g. 
   foreign import "C/stdcall" "gtk:foo" foo :: Int - IO
 Int
 
 2.  Treat C as one language, but put the calling convention into the
 language
 specific string.  E.g.
   foreign import "C" "stdcall/ gtk:foo" foo :: Int - IO
 Int
 
 
 I prefer (1) but it's not a big deal.  

I think, it was Malcolm who earlier argued that we shouldn't
have a language C, but rather name it ccall, because what we
really are after is the calling convention and not the
implementation language of an external function.  I would
regard this as an argument in favour of (1).  

BTW, We can't use "C/ccall" and "C/stdcall", as we decided
to not use a string, but a pseudo identifier to select the
language or rather calling convention.  So, it would be

  foreign import ccall "gtk:foo" foo :: Int - IO

In this context, I actually find it the identifier `stdcall'
strange.  Why is it standard?  I'd argue that ccall is the
standard (in fact, it so far was the default, wasn't it?)

Any suggestions for a better name?  Technically, it should
be `pascal' shouldn't it?  Is it good for anything, but
calling Win32?  Are there maybe Pascal compilers that use
it?  If so, `pascal' would make sense.  Otherwise, we might
use `wincall'.  That's not really nice, but better than
`stdcall', I think.

If nobody comes up with a serious reason why we shouldn't,
I'll fix it to be 

  foreign import ccall "gtk:foo" foo :: Int - IO

and

  foreign import XYZ "whatever:foo" foo :: Int - IO

where XYZ is `pascal' or `wincall' depending on what gets
more support. 

Cheers,
Manuel

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



Re: FFI progress

2001-03-28 Thread Manuel M. T. Chakravarty

"Simon Peyton-Jones" [EMAIL PROTECTED] wrote,

 Here's my contribution to re-invigoration:
 
 As I recall the main sticking point is whether we have a global
 'foreign library' declaration in addition to foreign import etc.
 The main (only?) motivation for such a thing is
 
   C
 
 It's a powerful motivation because C is ubiquitous.  I do have
 one suggestion to elaborate our earlier proposal.  To remind you
 our simple-minded proposal was
 
 * no 'foreign library' decl
 * the c-language-specific string on a foreign import could say
   foreign import "gtk:foo" foo :: type
   with 'gtk' indicating which foreign package was indicated
 
 Main complaint was: the package-name = what-to-do mapping still isn't
 specified.  In short, our simple-minded proposal is too simple-minded to
 be useful.
 
 OK so the new suggestion is this: the 'gtk' indicates 'please #include
 gtk.h'.
 It's up to you to have a 'gtk.h' lying around, in which you can put all
 the 
 other #includes (including whether in  brackets or "" quotes) to your
 heart's content.
 
 I bet this still doesn't solve the problem entirely, but maybe it solves
 enough
 of the problem.  I remain reluctant to generate elaborate designs for a
 single
 language.

I completely agree that we should have a simple solution and
achieve more convenient interfaces via the existing FFI
tools.

I propose the following (basically my last proposal plus
suggestions made by others):

  foreign import "gtk.h:foo" foo :: type

corresponds to a `#include "gtk.h"' and

  foreign import "gtk.h:foo" foo :: type

corresponds to a `#include gtk.h'.  The former allows to
have a custom `gtk.h' "lying around" as suggested above.
The filename may of course be a path.

As suggested by SimonM, we also allow multiple includes
seperated by comma

  foreign import "sys/types.h,sys/sockets.h:socket" socket :: type
  
(This could be solved by a custom header, too, but IMHO
allowing a list of headers doesn't complicate the
implementation much, but makes a common case more
convenient.)

foreign import/export modifiers like unsafe and dynamic can
be in arbitrary order (proposed by SimonPJ).

"foreign export dynamic" requires a result type of the form

  IO (FunPtr prim_type)

(proposed by Sven).

(Of course, concrete implemenatations - like the one in GHC
and nhc - may support the old syntax for backward
compatibility.)

Rationale
~
This is easy to implement and as close as possible to the
current syntax while still being better suited for multiple
languages.  It is not as flexible as the proposal from
Marcin and Malcolm, but significantly simpler.  More
sophisticated interfaces can be realised on top of the basic
FFI interface by tools.

Proposed decision procedure
~~~
I propose that if nobody can come up with an important
scenario that cannot be implemented with the above proposal,
we adopt the proposal.  (Here "cannot be implemented" means
technically infeasable, not less convenient.)

If we adopt the proposal, I will define it in detail.

Cheers,
Manuel

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



Re: FFI progress

2001-03-28 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote,

 Wed, 28 Mar 2001 12:10:46 -0700, Alastair Reid [EMAIL PROTECTED] pisze:
 
  If most libraries could be ffi'd without the need for additional C files, the
   multiple header file notation would be an obvious win.
  
  As it is, many libraries I've dealt with need one or more .c files containing
   some support code and, in that case, it's not too big a deal to add another file.
 
 I think that since usually there is a C header associated with the
 module, it's not a problem to put original C headers there. I prefer
 minimal header information at each foreign declaration, so it would
 refer only to the custom module.

I have usually not needed an extra (custom) header file
associated with Haskell modules, but maybe the libraries
that bound where just exceptionally well behaved.

"Alastair Reid" [EMAIL PROTECTED] wrote,

foreign import "foo.h,bar.h:f" f :: type
foreign import "bar.h,foo.h:f" g :: type
 Should I report an error?
 
 Or, suppose I have:
 
foreign import "foo.h:f" f :: type
foreign import "bar.h:g" g :: type
foreign import "foo.h:h" h :: type
 
 can I assume that foo.h will only be included once?
 can I assume that foo.h is included before bar.h?
 
 (When answering, remember that an optimising compiler might combine code from
  multiple modules (possibly with multiple maintainers) into a single C source
  file due to cross-module inlining.)

That's a very good argument in favour of SimonPJ's proposal,

 Its easy to add features and nigh impossible to remove them. 
 I suggest we have just
 
   "gtk:foo"
 
 (no ".h") meaning 
   #include "gtk.h"
 Now we can sensibly interpret "gtk:foo" as meaning "foo from package
 gtk";
 and in concrete terms import a suitable header file.

Ok.  I think, this scheme is sufficient and Alastair has
pointed out the semantic difficulties of a more complex
scheme.  Moreover, Marcin seems to favour it, too.
Any objections? 

Manuel

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



RE: unsafePerformIO and unsafeInterleaveIO

2001-03-21 Thread Manuel M. T. Chakravarty

"Alastair Reid" [EMAIL PROTECTED] wrote,

  Without a standard way to get
  at unsafePerformIO, such code would still rely on
  non-standard features, which goers against the aim of
  standardising the rest of the FFI.
 
 The Hugs-GHC standard libs have them exported from IOExts.
 
 Of course, the Hugs-GHC standard isn't an official Haskell library committee 
approved standard but, since it's something like 4
 years old, I think it's a better candidate for approval than the ffi library which 
hasn't really stabilised yet, hasn't been whacked
 on by a large number of users, is much younger, etc.

There is only one flaw: It doesn't work with nhc98.

I'd really prefer to keep the FFI stuff self-contained and
have it work on ghc, Hugs, *and* nhc.

Cheers,
Manuel

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



Re: unsafePerformIO and unsafeInterleaveIO

2001-03-19 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote,

 Mon, 19 Mar 2001 11:04:43 -0700, Alastair Reid [EMAIL PROTECTED] pisze:
 
   Should these functions be available through the standard FFI?
   IMHO they should.
  
  I don't understand the question.
  Are you asking which modules should export them?
 
 Yes. IMHO they should be made as "standard" as the rest of FFI
 and exported from module Foreign.

I guess, you could a (maybe inefficient) version of
unsafePerformIO using the FFI functionality anyway.  This
gives us a default implementation, so I thing, we should
include it.  I am not so sure about unsafeInterleaveIO.

Manuel

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



RE: Summary of current change suggestions

2001-02-22 Thread Manuel M. T. Chakravarty

"Alastair Reid" [EMAIL PROTECTED] wrote,

  So, as Marcin pointed out, the only use for a library object
  spec for ccall is so that interpreters know which handle to
  pass to dlsym().
 
 This may be the only use but I think it's a very important use.
 
  I am not too fond of the idea that the interpreter has to try
  a dlsym() on all library objects that it did dlopen().
  Or is this maybe not too bad?
 
 I think it's just asking for trouble (for reasons given in earlier mail).

Marcin just pointed out that you can use dlopen() in a way
that it finds symbols without a library name.  That should
do, I think.  

Cheers,
Manuel

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



RE: Summary of current change suggestions

2001-02-22 Thread Manuel M. T. Chakravarty

"Simon Marlow" [EMAIL PROTECTED] wrote,

 
  * specifying libraries in the source isn't the right way to
go.  Library names change independently of APIs, and can be
platform-specific.
  
  I like the high level goal this is heading towards and was in complete
  agreement with implementing it in rules like this until  
  I realised that
  all that Hugs sees is the source (i.e., there's no makefile 
  to put extra
  compilation info into) - so if it ain't in the source, where is it?
  
  But I like the rule...
 
 Well... there's no reason why hugs couldn't use something like GHC's
 packages.  In fact, it could use the scheme largely unchanged; but
 perhaps the package spec should be extended to include a path to source
 files (the alternative is to overload the path to the interface files
 and put the sources in the same place if you want to share a package
 between Hugs  GHC).

I think, a path to source files would be a good idea.

Cheers,
Manuel

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



RE: Summary of current change suggestions

2001-02-22 Thread Manuel M. T. Chakravarty

"Alastair Reid" [EMAIL PROTECTED] wrote,

  Marcin just pointed out that you can use dlopen() in a way
  that it finds symbols without a library name.  That should
  do, I think.
 
 Note that finding a marginally easier way to do the lookup doesn't address my
 concern that this undirected search will cause maintenance and porting problems
 by worsening an already bad situation (just which library did
 Linux/solaris/freebsd/hpux/redhat6.0/redhat7.0/... choose to hide a symbol in).
 
 In fact, I expect that having dlopen do a search through the libraries that it
 thinks are relevant instead of Hugs performing a search through the list of
 libraries that it knows to be relevant probably makes things worse because it
 increases the gap between the programmer's mental model and what actually
 happens.
[..]
 ps dlopen is not completely portable - Hugs also uses shl_{load,findsym} (HPUX
 only?) and {LoadLibrary, GetProcAddress} (Win32).

Fair enough, but as I pointed out.  Adding a library name to
the import declaration also doesn't work in all cases.  So
we have one ad-hoc, half-backed solution against another.
In this case, I would prefer the simpler one (which
obviously is not to specify anything, as we can't properly
specify it anyway).  Unless, we find a third, actually
working solution of course.

Manuel

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



RE: Modification to foreign import/export

2001-02-20 Thread Manuel M. T. Chakravarty

[Better a late answer than none :-/ ]

"Alastair Reid" [EMAIL PROTECTED] wrote,

  This has the advantage that when the library name is #ifdefed, the
  conditional needs not to be repeated for each function. Similarly
  for #included header names.
 
 Note that this can be done without separating the library name from the ffi
 decl:
 
 #ifdef UNIX
 # define LIBNAME "foo.so"
 #else
 # define LIBNAME "foo.dll"
 #endif
 
 foreign import ... LIBNAME ...
 foreign import ... LIBNAME ...
 foreign import ... LIBNAME ...

That's not a solution, because cpp is not part of Haskell.
I think, it is a good idea to make things cpp-friendly where
we can, but we must not rely on cpp to solve any problem.

 I think I missed the motivation for extending the ffi to
 support other languages. 

We believe that by making the existing design a little bit
more modular and general, we can add the potential for
adding new languages at will without affecting any existing
part of the definition.  So, we want to move from a closed
C-sepcific design to an open and extensible one.  In the
process, we want to get rid of some current weakness (like
the issue of specifying headers), too.  That doesn't means
Hugs has to support any Java stuff (if this is what you are
worrying about).  In fact, it is entirely possible (as you
propose) to have a tool that rewrites a Java binding to a
JNI-binding going via C.

In a related point.  I agree that we have to keep backwards
compatibility in the implementations for a while, but the
whole FFI design was always experimental, which means that
it changes a couple of times until it is settled down.  I
have lots of code that I have to rewrite because of this,
too.

We are pretty happy with the libraries now.  There remains
some tweaking with the declarations, and then, the plan is
to write the definitive FFI definition and get it "approved"
by the community and that's it.  Then, we treat it like H98,
a fixed standard that has to be supported.

Cheers,
Manuel

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



ANN: C-Haskell 0.8.1

2001-02-11 Thread Manuel M. T. Chakravarty

I am pleased to announce the availability of version 0.8.1
of the interface generator C-Haskell.  It works with the
current stable release series 4.08.x of GHC as well as the
current development series 4.11.  For both versions of GHC,
it supports the *same* FFI library that GHC natively only
supports in the development version 4.11 and which
constitutes the result of the work of the FFI Task Force
over the last couple of months.  The interface specification
of the library is online available at

  http://www.cse.unsw.edu.au/~chak/haskell/c2hs/docu/c2hs-4.html

For more information on C-Haskell and for downloading, see

  http://www.cse.unsw.edu.au/~chak/haskell/c2hs/

The main feature in this release is the new FFI library.  It
should allow users of the GHC stable series to use the new
FFI library interface, which we hope to keep stable from now
on.  An update of the C-Haskell tool proper is being worked
at.

Happy Hacking,
Manuel

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



Re: Typing f.e.d.

2001-02-11 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 I have a small change request regarding foreign export dynamic.
 Currently the FFI doc says:
 
topdecl 
: ...
..
| 'foreign' 'export' [callconv] 'dynamic' varid :: prim_type - IO Addr
 
 GHC additionally allows:
 
prim_type - IO Ptr
 
 As usual the FFI "looks through" newtypes.  But now that we have
 FunPtr, the following typing makes much more sense:
 
'foreign' 'export' [callconv] 'dynamic' varid :: prim_type - IO (FunPtr 
prim_type)
 
 where both prim_types have to be the *same*. We should probably allow
 the old Addr-typing as well for some time to facilitate the transition,
 but not the Ptr-typing (bleeding edge people will know what to do :-).
 The corresponding changes to GHC look easy, so I'd like to commit this
 if there are no objections.
 
 Furthermore, the FFI docs still talk about Addr only, not Ptr/FunPtr.
 Now that Addr is deprecated, this should be changed, too.

Yes, Addr is dead.  So, allowing Addr in f.e.d., or anywhere
else for that matter, can only be for reasons of temporary
backward compatibility.

Cheers,
Manuel

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



RE: Let's get this finished

2001-01-10 Thread Manuel M. T. Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

  "Manuel M. T. Chakravarty" wrote:
   If hslibs is meant to be used with systems other than ghc,
   too - which I think was the idea - there is no choice but to
   rewrite it into H98.  But I guess this is essentially up to
   Mr. HsLibs aka SimonM.
  
  Well, doing some simple local transformations to get H98 compliance
  should be possible without consulting Mr. HsLibs in advance.  :-)
 
 [ blimey.  I go away for a couple of days and you guys are going
 bananas.  Slow down! ]

Too late.  I just checked in the last module.[1]  (And besides,
I thought you wanted to get this done...)

 I should say that I've recently been working on moving most of the FFI
 code into ghc/lib/std, removing GHC's use of deprecated features (eg.
 using Ptr instead of Addr), and converting some of GHC's standard
 libraries to use the new FFI.  Directory has been converted so far.

I don't see a problem moving the new stuff there, too (if
you need it).

 I think there's no alternative to having two copies of much of the code
 - a H98 version in hslibs/lang and GHC-specific code partly in
 ghc/lib/std and partly in hslibs/lang, with appropriate #ifdefs.  We'll
 need to set up a way to test the H98 code using GHC too.

I can understand (dependency-wise) that you want to have
some of the stuff in ghc/lib/std.  However, why don't leave
it in H98.  Having local functions instead of pattern type
annotations doesn't look as nice, but otherwise shouldn't be
a problem.  In some places (like in CError), there are some
#ifdefs to use GHC specific features.

(The story is a bit different for the older system dependent
modules, but they are...aehmm...system dependent, anyway.)

 I don't see any problem with using hsc2hs for the H98 versions, since
 hsc2hs is mostly compiler-independent.  (but I notice you've used
 autoconf instead of hsc2hs for the errno code.  I haven't looked at it
 yet.)

Figuring out how to do loops in aclocal.m4 was easier than
getting the make system to call hsc2hs at the right point
:-)

Besides, IIRC Malcolm said that he isn't to keen on another
tool.

BTW, Malcolm, I think, all the new code should work in NHC
if you want to try.  The main problem is getting the
constants for the error codes as you don't use autoconf for
NHC.  

Cheers,
Manuel

PS: Yes, I'll write sgmls for the new modules, too.

[1] For those who are not on cvs-hslibs, the additional
marshalling modules that we discussed here recently can
be inspected in the fptools/hslibs repository.

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



Re: Let's get this finished

2001-01-09 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote,

 Tue, 09 Jan 2001 13:59:10 +1100, Manuel M. T. Chakravarty [EMAIL PROTECTED] 
pisze:
 
  I was thinking of having the library itself by default
  provide a set of standard encodings.  Like - as you say
  later - we usually rely on a set of standard MIME encodings
  to be available.

 If an encoding is added to the database at some point of time,
 a program uses it and is then recompiled on a system which does
 not provide this encoding, you get a runtime error.
 
 If conversions are referred to as plain imported values, you get
 a compile error.

But what would be the reason for an implementation not
providing this conversion?  That it can't do the conversion?
But in this case, you have a problem anyway.  Independent of
the mechanism used to reference the conversion, you won't
get it.  This not different from trying to print Cyrillic
text on a computer that doesn't have a Cyrillic font - you
just won't see much :-)

Other than that, your library could explicitly list a set of
standard conversions that any complying implementation has
to provide (at least if it is available on the system).

 A database is only useful if encodings are now known individually
 by the programmer and he wants his program to support everything
 the Haskell's library provides for some well known name scheme. It
 can be a convenience wrapper, but definitely not the basic reference
 for conversions.

I did mean it as a convenience wrapper.  There are certainly
users who want the full interface.  I am just thinking about
the average user writing an average program who happens to
write all error message in Mandarin.  This person wants an
easy way to access Big5 somehow, not more.

Cheers,
Manuel

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



Re: Let's get this finished

2001-01-07 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote,

 Sat, 06 Jan 2001 22:37:35 +1100, Manuel M. T. Chakravarty [EMAIL PROTECTED] 
pisze:
 
  If there were a faster alloca, it would still speed up the
  common case where there is no conversion or the initial size
  estimate is correct.
 
 I'm afraid the common case includes a conversion.

Why?

Manuel

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



Re: Let's get this finished

2001-01-07 Thread Manuel M. T. Chakravarty

Sven Panne [EMAIL PROTECTED] wrote,

 Marcin 'Qrczak' Kowalczyk wrote:
  [...] If language separation is realistic, we would also keep
  errno handling outside basic Foreign.
 
 Hmmm, indeed. `CErrors' or `CErrno' would be a good name IMHO.

`CError' by our current naming scheme.[1]

  But it yields several separate C-specific modules...
  
  module CForeign?
  
  It would reexport Foreign, CTypes, CTypesISO, MarshalCString and
  CErrors (or whatever they will be called).
 
 I'd second that (with the small addition that MarshalCString is
 replaced by CString/CStringLen).

BTW, shall we really seperate CString and CStringLen into
two different modules?  I am all for modularisation, but in
this case I am not sure whether it is worth it.

Cheers,
Manuel

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



freeHaskellFunctionPtr

2001-01-02 Thread Manuel M. T. Chakravarty

I propose to deprecate `freeHaskellFunctionPtr' in Foreign.
Equivalent functionality is now available from
`Ptr.freeHaskellFunPtr'.  Normally, we have all `Ptr'
functionality also in a variant for `Addr', but in this
case, this doesn't make sense in my opinion.  The reason is
that `Addr' is there as a backup solution when `Ptr' doesn't
fit.  But if a `Addr' is used to represent a Haskell
function pointer, I don't see a reason that `Ptr.FunPtr'
could not have been taken.

If there are no objections, I will deprecate
`freeHaskellFunctionPtr' in `Foreign'.

Cheers,
Manuel

PS: It could be argued that `Ptr ()' can always be used
instead of `Addr' and that therefore we should do away
with `Addr' altogether.  Opinions?

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



Re: extended foreign decls

2001-01-02 Thread Manuel M. T. Chakravarty

Fergus Henderson [EMAIL PROTECTED] wrote,

 On 02-Jan-2001, Manuel M. T. Chakravarty [EMAIL PROTECTED] wrote:
  [This comment is a bit late, I know...]
  
  [EMAIL PROTECTED] wrote,
  
   Fergus writes, triggered by my suggestion of "foreign value":
   
Mercury supports this using `foreign_decls' and `foreign_code' pragmas.
   
   I refrained from proposing this in an earlier mail, but I've been
   thinking about it for a long time.  I *really* *really* want to be
   able to insert small snippets of foreign code into the source of
   a Haskell module.
   
   GreenCard allows you to do this, via the %- or %C directives.  It is
   one of the features I miss most about the new FFI.  I know that it
   is always possible to write a small .c file and compile and link it
   in separately, but with the new FFI that now seems to necessitate
   writing an additional .h file as well.  And all for a handful of lines
   of foreign code that could easily be kept in the Haskell source, with
   the ease-of-comprehension benefits entailed by keeping everything
   together that belongs together.
  [..]
  
  I believe that functionality like this should be implemented
  by an extra tool rather than the Haskell compiler.
 
 Doing it in a separate tool will lose efficiency in some important
 cases.  If the compiler is compiling via C, then it can insert
 inline C code directly in the generated code, and thus get
 inlining.  But I think a separate tool would have to put the C code in
 a separate C file, which would prevent inlining.

This has some problematic consequences:

* Code which replies on this inlining would require any
  high-performance Haskell compiler to compile via C.

* As I understand, these pragmas are supposed to support not
  only C.  How about C++ code?  Will there be a C++ backend
  for Mercury just to make this code efficient?

Cheers,
Manuel


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



  1   2   >