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
assume that a pointer difference fits into an `Int' (what we
do at the moment) is pretty dodgy.  Remember that all that
H98 requires of an `Int' is that it has >=30 bits.  IMHO,
this is pretty weak for a general representation of a
pointer difference.

The annoying thing about our old use of `PtrDiff' was that
it made `plusPtr' a pain to use (as we had to cast the
offset to a `PtrDiff' first).  A simple solution would be

  plusPtr :: Integral i => Ptr a -> i -> Ptr b

I am actually pretty convinced that this is the right way to
go.

Argument types for foreign functions
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
As you can see, I have removed my construction for using
`Storable' to specify the types that can be used as
arguments to foreign functions.  However, I don't agree with
the posts claiming that this route would be unworkable.
Whenever a type `T' is `Storable', it can be passed to a
foreign function in one of two ways:

(1) The compiler has special knowledge about the type and
    just generates the normal (possibly type-dependent)
    argument passing code.

(2) If the compiler has no special knowledge about the type,
    it `alloca's temporary storage for the type and `poke's
    the argument into that location.  Then, it generates a
    stub routine in the foreign language that gets a pointer
    to the temorary storage instead of the actual argument.
    The stub routine extracts the argument and calls the
    actual foreign routine.

The idea is of course that the compiler (at least if it
aspires to generate decent code) has special knowlegde about
all the standard types.  So, (2) is only the fallback for
weird user-defined instances of `Storable'.

(+) I like this approach, because it makes the FFI
    definition nicer.

(-) Unfortunately, it is more fuss for the implementation
    and probably doesn't make a big difference in practice.

I have removed it from the report, because "worse is better"[1]
(at least that's what some people claim; although it is
somewhat against the spirit of Haskell, which tends to put
elegance over simplicity of implementation).

[1] http://www.jwz.org/doc/worse-is-better.html

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

Reply via email to