RE: HDirect + String Arrays.

2000-08-21 Thread Simon Peyton-Jones

I'm forwarding this to the FFI list in the hope that
someone can help Chris.

Simon

| -Original Message-
| From: Chris Ryder [mailto:[EMAIL PROTECTED]]
| Sent: 11 August 2000 12:05
| To: Simon Peyton-Jones
| Subject: HDirect + String Arrays.
| 
| 
| Hi,
| 
| I'm trying to call a C function from Haskell (GHC 4.04, 
| HDirect 0.16) that
| returns an array of strings. eg :
| 
| char **myCfunc(void);
| 
| or, perhaps :
| 
| void myCfunc (int* size, char*** array);
| 
| I have an IDL file that specifies :
| 
| module Thing {
| void myCfunc([out]int* asize, [out,string,size_is(asize)] 
| char*** arr);
| };
| 
| This generates marshalling code that looks correct (its shown 
| at the end
| of this message) but when run, only the first string seems to 
| be correctly
| marshalled - all subsequent strings in the array become NULL 
| (represented
| as Nothing ?) The strings are definatly allocated in the C 
| function, so
| I'm sure it is a marshalling problem.
| 
| Is there something I'm missing or doing incorrectly ?
| 
| Many Thanks,
| Chris Ryder.
| 
| --- Haskell code generated by ihc ---
| 
| -- Automatically generated by HaskellDirect (ihc), snapshot 300600
| -- Created: 11:41 BST, Friday 11 August, 1900
| -- Command line: -fhs-to-c Test.idl
| 
| module Thing
|( doSomething
|) where
|
| import qualified Prelude
| import qualified Addr (Addr, addrToInt)
| import qualified HDirect (sizeofInt32, allocBytes, sizeofAddr, 
|   readInt32, readString, readunique, 
| int32ToWord32, unmarshalllist, 
|   free, doThenFree)
| import qualified GlaExts (toInt)
| 
| doSomething :: Prelude.IO [Prelude.Maybe Prelude.String]
| doSomething =
|   do
| asize <- HDirect.allocBytes (GlaExts.toInt HDirect.sizeofInt32)
| query <- HDirect.allocBytes ((GlaExts.toInt 
| HDirect.sizeofAddr Prelude.* Addr.addrToInt asize))
| prim_Thing_doSomething asize query
| asize <- HDirect.readInt32 asize
| HDirect.doThenFree HDirect.free (HDirect.unmarshalllist 
| HDirect.sizeofAddr 0 (HDirect.int32ToWord32 asize) 
| (HDirect.readunique HDirect.readString)) query
| 
| foreign import  "doSomething" prim_Thing_doSomething :: 
| Addr.Addr -> Addr.Addr -> Prelude.IO ()
| 
| 




RE: qforeign-0.62

2000-11-28 Thread Simon Peyton-Jones

Dear foreigners

Simon and I noticed this morning that ForeignObj should
really be parameterised.  The current type of newForeignObj is

  newForeignObj :: Ptr a -> IO () -> IO ForeignObj

This immediately loses the type information on the Ptr!
Shouldn't it be

  newForeignObj :: Ptr a -> IO () -> IO (ForeignObj a)

Or maybe we should shorten it to (FPtr a)?  ("F" for "finalised".)

Similarly
  withFPtr :: FPtr a -> (Ptr a -> IO b) -> IO b

It's bizarre to have
   withForeignObj :: ForeignObj -> (Ptr a -> IO b) -> IO b


What think you?

Simon

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



RE: qforeign-0.62

2000-12-01 Thread Simon Peyton-Jones

| So, how about the following?  Instead of the 
| 
|   newtype Window = Window ForeignObj
| 
| way of wrapping foreign ADTs that we used so far, should we
| use
| 
|   newtype WindowTag = WindowTag ()
|   typeWindow= ForeignObj WindowTag

A fine idea.  I accept what you say about ADTs, but
if it's really so, we woudn't need the objectionable 

>withForeignObj :: ForeignObj -> (Ptr a -> IO b) -> IO b

because all ForeignObj-manipulating things would be foreign
imported

foreign import f :: Window -> IO ()

Anyway, it strikes me as good to tag each ForeignObj with
an indication of what it points to, just so that one does not mix
up ForeignObjs that should not be mixed.

But it's just a suggestion.  You guys who are deeply into the FFI
should decide.

It would be nice to get to closure on this FFI stuff -- it's been going on
a long time!

Simon


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



FW: H/Direct

2000-12-06 Thread Simon Peyton-Jones

Here's a question from Koen that bears on the FFI.

Simon

-Original Message-
From: Koen Claessen [mailto:[EMAIL PROTECTED]]
Sent: 04 December 2000 12:55
To: Erik Meijer; Simon Peyton-Jones; Sigbjorn Finne
Subject: H/Direct


Hi H/Direct team,

I have been using H/Direct for quite a while now, and I am a
happy user (apart from the massive amount of work involved
in getting the system to run for both Hugs and GHC -- there
seems to be a circular import which Hugs complains about and
which can be skillfully removed, but which GHC depends on or
something.)

I have a question about marshalling arguments which are
expensive to marshall in H/Direct. Often you want this
result to be shared between calls of the functions.

Currently, I have applied the following technique a couple
of times and I wonder if it can be made more general and
added to H/Direct.

For example, I have a BDD package with the following
operation (I have simplified this type a bit):

  [pure]Bdd *BddReplace
( [size_is(n),in] int *xs
, int n
, [in]Bdd *bdd
);

(The argument "xs" encodes a variable mapping, which is used
to construct a new BDD from the argument.) I want this to be
a function in Haskell with the type:

  replace :: [Int] -> Bdd -> Bdd

The way I often use replace is by defining:

  prime :: Bdd -> Bdd
  prime = replace [ extremely-long-list ]

Here, I want the marshalling of the list to happen once, and
to be shared between calls to prime.

So I wrote my own version of replace in Haskell. Here it is:

  replace :: [Int] -> (Bdd -> Bdd)
  replace xs =
unsafePerformIO $
  do array <- newCArray (length n)
 sequence [ setCArray array i x
  | (i,x) <- [0..] `zip` xs
  ]
 return (\bdd -> primBddReplace bdd array)

Note the brackets in the type to indicate I am returning a
function. Now, the CArray interface must look like this:

  [finaliser("free")]
  interface CArray {};

  CArray *newCArray( int n );
  void   setCArray( CArray *arr, int i, int n );
  intreadCArray( CArray *arr, int i );

This is because "replace" should not free the C-array until
it looses track of the returned function.

It works great! The question is: can this be done by
inventing some new annotation for the IDL code? One problem
is maybe that the sharing of these things can only be done
in a certain order.

Regards,
Koen.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden

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



RE: extended foreign decls

2000-12-07 Thread Simon Peyton-Jones

| For ("preferred" language, foreign language) pair, you define an
| "extrusion".  This defines how to generate the appropriate code to 
| interface with one foreign language in another.  

All sounds very ingenious.  Much of it, though, is quite Mercury
independent.
As you say, it's a way of making the Mercury compiler think it's only
talking to C.

Obvious question: do you plan to package your solution as a reusable
tool, so that others can profit from its ingenuity?

Simon 

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



RE: Typing f.e.d.

2001-02-13 Thread Simon Peyton-Jones

This looks plausible to me too --- but I agree with Alastair
that we should not remove support for Addr, including in f.e.d.
Backward compatibility is a pain, but lack of is a fast way
to lose customers.

Simon

| -Original Message-
| From: Sven Panne [mailto:[EMAIL PROTECTED]]
| Sent: 11 February 2001 16:01
| To: The Happy Bit Fiddlers
| Subject: Typing f.e.d.
| 
| 
| 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.
| 
| Cheers,
|Sven
| 
| ___
| FFI mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/ffi
| 

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



RE: Summary of current change suggestions

2001-02-22 Thread Simon Peyton-Jones

I must say that I like Manuel's proposal below.  I'm a bit alarmed
about the proliferation of features in the FFI, but Manuel's story
makes it seem more tractable.  It's in the spirit of putting all
the language-specific info needed for a particular foreign import
into a single string.  

The FFI spec should have a section specifying the syntax of this
string for a selection of languages.

Incidentally, we should make the order of 'import/export' , 'dynamic',
'unsafe' keywords arbitrary.  So you should be able to write
foreign import unsafe dynamic ...
or
foreign import dynamic unsafe  ...

I'm not sure exactly which the unordered set should be, maybe
the optional components.

Simon

| I am still against cpp, but maybe we can relegate defaults
| to the tools domain in general (and whoever is fond of cpp,
| can use cpp).  Without defaults, it is still possible to use
| all features of the FFI.  If a user wants the convenience of
| defaults, she has to use a tool (as with all the other
| "features" that we considered too heavy for the core FFI).
| 
| Then, we could use the following general form of foreign
| imports:
| 
|   foreign import [callconv] [funname] ['unsafe'] varid :: prim_type
| 
| where funname is calling-convention dependent and in the
| case of ccall is either merely the name of the imported
| symbol or an include specification followed by a colon and,
| then, the imported symbol.  So, we have
| 
|   foreign import ccall "gtk_window_new" 
| windowNew :: CInt -> IO (Ptr Window)
| 
| or
| 
|   foreign import ccall ":gtk_window_new" 
| windowNew :: CInt -> IO (Ptr Window)
| 
| If the <.> are omitted in the include specification, it
| corresponds to an #include"...".


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



RE: Typing f.e.d.

2001-02-22 Thread Simon Peyton-Jones

What became of this suggestion of Sven's?  Did we adopt it?
(While deprecating but not dropping Addr.)

Simon

| -Original Message-
| From: Sven Panne [mailto:[EMAIL PROTECTED]]
| Sent: 11 February 2001 16:01
| To: The Happy Bit Fiddlers
| Subject: Typing f.e.d.
| 
| 
| 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.
| 
| Cheers,
|Sven
| 
| ___
| FFI mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/ffi
| 

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



RE: Modified proposal for default decls

2001-02-26 Thread Simon Peyton-Jones

| I am reasonably convinced by the need for an extensible 
| attribute-style specification such as Marcin has been proposing. 

I've been talking about the FFI stuff with Simon and Julian.
We aren't (yet, anyway) convinced by the need for anything 
nearly as elaborate as what is now proposed.

Most notably, Malcolm's latest proposal introduces a new form
of abstraction (named thing), a bundle of attributes like Gtk or Bzip.
Another environment for the compiler to manage! Soon people will
want to export these things and import them elsewhere!This 
way lies madness.

What is particularly tanatlising is that to a first approximation none
of this is necessary.  For example, the native code generator is quite
happy without any of the new stuff now proposed.

I think we can usefully distinguish three kinds of thing:

a) What is necessary to uniquely identify the thing you want to call.
In C this is just a single identifier; in Java, it's a fully
qualified
   method name, plus the method type.  Other languages doubtless
   lie between

b) What is necessary to allow the compiler to typecheck the 
foreign import/export.  In part, we seek #includes so that 
   in the via-C route the C compiler will compare the call with the
   prototype, and complain if they don't match.  But this is an
implementation
   thing. In principle, the Haskell compiler could consult type info and
   compare.  The important thing is that there's enough info to get from
   the thing-being-called to the type-of-the-thing-being-called.

c) What is necessary for particular compilers, compiling in a particular
way,
   to generate the right code.  In particular, GHC compiling via C.  GHC
  can't generate prototypes, because they might be #included.  GHC can't
  omit prototypes unless prototypes are guaranteed to be #included.  
  Hence the motivation to specify #include stuff.


Notice that
a) is essential
b) is desirable, but not implemented at all
c) is essential, but extremely language and compiler specific

Therefore we propose that
a) be part of the FFI standard
b) be achievable, if desired, via (a)
c) be not part of the FFI standard

In particular, we propose to stick to a mild variant of the current FFI
story

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

* "ccall" is one of a small number of language specifiers, "java" and
".net"
   "stdcall" being other possibilities.  C is strange in having more
than one calling
   convention; we treat "stdcall" as a second "language".

* The "gtk:foo" is a string in language-specific format 
   that uniquely specifies the thing being called.  It'll be quite
different for Java,
   when it'll contain the type signature of the method and whether it's
a "new"
   constructor etc.

*  The "gtk:" part is a concession to (b).  It specifies a C package
from which 
   this procedure comes. There is then some compiler-specific mechanism
   for mapping the name of a C package to the location of its header
files and
   .o file.

* If the Haskell compiler wants to typecheck the import, it is free to
consult
  the header file, meta data or whatever, based on the foreign package
name
  and the name of the thing being called.


No "foreign library",  no "foreign default"...  You get to repeat
everything at
every foreign import.  Notice that cross-module exports of inlinings are
now
straightforward: the foreign call carries its package name with it.


You may think this is too minimalist, but there are big advantage to
simple,
minimal designs, even if they can't cope with every single case.  Do we
really
need the elaboration of Malcolm's proposal?

Simon

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



Libraries and FFI

2001-03-23 Thread Simon Peyton-Jones

| I would also want to echo Simon's comment that the new hierarchical
| namespace and library proposal should go a long way to making the
| library situation better in the very near future.  We are currently
| discussing a general layout and re-naming of the existing modules from
| hslibs.  If Hugs users and developers don't join in the discussion,
| then we could be wasting our effort.  We really want to develop
| a de-facto cross-compiler standard, not just a one-compiler or
| two-compiler standard.

...and indeed, no one from OGI is subscribed to either the FFI or the 
Libraries discussion list.  I'm ccing some of them so they can take 
a look at the thread:
http://haskell.org/pipermail/ffi/2001-March/thread.html
http://haskell.org/pipermail/ffi/2001-March/000270.html

Staying out of these discussions is a perfectly reasonable choice
on their part (there are only so many hours in the day) but it does mean
that it's unreasonable to expect Hugs to track either debate.

In the minutes of the Haskell Implementors Meeting in Jan we had:

Hugs:   OGI in maintenance mode.  There's a danger that Hugs
will
gradually die, which none of us want.  One idea: advertise
openly for a home for Hugs.  JOHN will take this
suggestion to OGI.

John, did anything come of this?


Simon

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



FFI progress

2001-03-23 Thread Simon Peyton-Jones

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?
We don't have a plan at the moment; nor do we have even a draft FFI
document (the one you are going to write!).  I'm concerned that
we'll just dribble on and lose morale.

Simon

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

Simon

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



RE: FFI progress

2001-03-28 Thread Simon Peyton-Jones

| I propose the following (basically my last proposal plus
| suggestions made by others):
| 
|   foreign import "gtk.h:foo" foo :: 
| 
| corresponds to a `#include "gtk.h"' and
| 
|   foreign import ":foo" foo :: 
| 
| corresponds to a `#include '.  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 ",:socket" 
| socket :: 

Do we really need this?  Surely it's not so hard to have one
header file per package living in a standard place that collects
the headers needed for a particular package, including whether
they are <..> or "...", etc.

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.  But I could
imagine
a clever compiler could also use to add gtk.a to the link line etc
(hence no .h).

Let's see if simplicity  is too painful.  I can't imagine it will be.

Simon


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



RE: FFI progress

2001-04-06 Thread Simon Peyton-Jones

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.

Might I suggest 
http://research.microsoft.com/~simonpj/ffi.html
as the basis for a state-of-play-summary.  You can grab the source
and modify it as you see fit.

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.

So that's ok, but we should agree that's what we want.

Simon

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



RE: FFI progress

2001-04-06 Thread Simon Peyton-Jones

One other thing.  What did we decide about the 'calling convention'
field.  I reckon it should vanish into the language-specific string,
or alternatively treat C as two languages that differ in their calling
convention.

No way C calling conventions deserve special treatment.

Simon

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



RE: FFI progress

2001-04-06 Thread Simon Peyton-Jones

Is anyone actually specifying 

stdcall
ccall

calling conventions in a foreign import?  I want to pull it
out of GHC but I don't want to break anything.

Simon

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



RE: FFI progress

2001-04-11 Thread Simon Peyton-Jones


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

Simon



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



RE: FFI Definition

2001-05-01 Thread Simon Peyton-Jones

|  * I'm not very happy with the fact that static/dynamic are 
| only viewed
|as modifiers, like unsafe/safe. They almost completely change the
|meaning of a foreign declaration, including the typing rules. In my
|view, we have *5* different language constructs: `foreign import',
|`foreign import dynamic', `foreign export', `foreign 
| export dynamic',
|and `foreign label'. 

|  * How will we differentiate between virtual vs. non-virtual 
| methods in
|the cplusplus calling convention? What about class methods vs.
|instance methods? Will these distinctions have influence on the
|typing rules? If yes, coding this into the extent would be wrong.
| 
|  * The JVM has *4* different instructions for method invocation
|(invokeinterface, invokespecial, invokestatic, and 
| invokevirtual), so
|our static/dynamic distinction seems a bit inflexible here. And the
|introduction of the "new" prefix looks like a hack, which doesn't
|even handle all situations.


These are good questions.  

I think it's inevitable that the form of type of the foreign thing is
going to depend on per-language details.  For C we have

call
call indirect
label

For Java we have

4 different invocations
new

For C++ we have 

call virt
call non-virt
new

Etc.  Each of these implies a particular form for the type.

I think we have to bite the bullet and put this stuff in the language
specific string, including our current static/dynamic thing.  The
compiler
has to be able to parse this string in order to generate an appropriate
call, so it's no big deal for this parse info to feed into the type
checker too.

This is moving in exactly the opposite of what Sven suggests, but I
don't
see any alternative.  My criterion is

language specific stuff inside the "..." string
language independent stuff outside

Simon

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



RE: FFI Definition

2001-05-02 Thread Simon Peyton-Jones

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

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

Simon

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



RE: FFI Definition

2001-05-07 Thread Simon Peyton-Jones

[Welcome back, Sigbjorn.  Are you on the FFI mailing list?
Now you are back online you should be!]

| Export dynamic introduces a name, export static exports an 
| existing name. For that reason putting this distinction in 
| extent seems strange for me.

This seems like a good point to me.

foreign export foo :: Int -> IO Int
exports a C-callable function foo
*uses* a Haskell function  foo :: Int -> IO Int 
(that is, foo must be in scope)

foreign export dynamic baz :: (Int -> IO Int) -> IO Addr
does not export anything to C
*defines* a Haskell function baz with the type specified
(that is, the foreign decl binds baz)

This is rather different to 'foreign import' vs 'foreign import dynamic'
both of which import a function, but the type of the function depends
on whether it's dynamic.


PRINCIPLE: it should be possible to look at a foreign decl, and 
*without looking at the extent string* say what Haskell function is
used or defined, and what its type is.   

CONCLUSION: we need to say outside the extent string whether
we are doing foreign export or foreign export dynamic.  I'm not
sure what the right syntax is

Simon

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



RE: Again: FFI syntax

2001-05-14 Thread Simon Peyton-Jones

| Comments? We should really come to an agreement on the syntax soon...

Generally, I like it.

| An open point is the last case of the include production: 
| Should we implicitly wrap double quotes around it or not? I 
| don't really like such implicit things, but
| 
| foreign import ccall "static !myproc \"myinclude.h\"" 
| myProc :: ...
| 
| could look a little bit funny because of the backslashes. 
| Again, I don't really mind about that topic. But I'm against 
| implicitly suffixing with '.h' in any case.

I'd go for automatically adding quotes.  Acutally, I'd automatically add
a '.h' too.  Reason: you are really specifying the assembly or package
where the function comes from, and that might be useful for linking as
well as includes.   If the package was called P, the compiler can
#include "P.h", and in addition say -lP on its link command.  That's
less
convenient if there's a .h to strip off.

Simon

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



RE: extent strings

2001-05-18 Thread Simon Peyton-Jones

A process comment:

  This FFI discussion is dragging.  I really want to
   get a conclusion because I want to implement it
   for .NET.  Manuel --- you are are Tzar.  Whip us
  into order!

(I don't think that any of the issues are do-or-die ones; i.e.
compromise is possible!)

| > > [...] What's the advantage of putting the information in a string?
| > [...] This is useful for tools that parse Haskell source code but 
| > which are not compilers -- e.g. documentation generators.
| 
| That's not really an argument, because if we slightly change 
| the grammar, a "catch-all" production is easily specified:

But only if the catch-all production catches all. For example,
suppose we wanted to specify the full type signature of a Java
function. In principle we could specify a grammar that would
describe

foreign import jvm 
static int Java.Lang.foo( int x ) 
foo :: Int -> IO Int

But it's hard to parse without the newline, and it's going to
be hard to specify a catch-all syntax that enables the documentation
generator to skip all the jvm-specific junk.

I think we should stuff it into a execution-platform-specific string, 
thus

foreign import jvm 
"static int Java.Lang.foo( int x )"
foo :: Int -> IO Int

What should be visible "outside" the string.  I think:

a) what Haskell function is being defined or used
b) what the Haskell type of that function is
c) whether the function is being *defined* 
(like foreign import or foreign export dynamic)
or *used*
(like foreign export)

Haskell functions that are *used* must be in scope already;
those that are being *defined* are brought into scope by the 
foreign decl.

Unfortunately, 'foreign export dynamic' defines a function, so
one cannot just look at the import/export keyword.

Maybe we need
foreign import
foreign export
foreign dynexport
?

(Dynamic import is quite different; it's still an import, but there's
one more argument.)


Simon

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



RE: Again: FFI syntax

2001-05-30 Thread Simon Peyton-Jones

| > Just to restate my position: I'm against *always* wrapping 
| the header 
| > file name in double quotes, unless
| > 
| >#include "foo/bar.h"
| > 
| > implies
| > 
| >#include 
| > 
| > if the first form is not found.
| 
| It does, but having "" and (ab)using it to mean <> would be 
| bad - if the current directory happens to contain a file with 
| such name then confusion begins.

I've not been following this discussion in detail, but I note that

* IN GENERAL one might like

to include multiple header files (#include foo.h; #include
bax.h)
to incude files from other directories (#include foo/bar.h)
to #define things (#define DEBUG; #include foo.h)
to change the search path (#include )

* But all of these things can be done in a C header file. So all we
*need*
  is the ability to include a single header file, gotten from the
current directory

foo.h

So why not keep it simple?   Just one header file, no directories, no
search
path, no <> brackets.  Any of that stuff can be done in the file you
#include


Meta comment: this point is not large enough to justify a great deal of
effort or delay.

Simon

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



RE: FFI Report, CVS Id 1.4

2001-06-05 Thread Simon Peyton-Jones

| Subject: FFI Report, CVS Id 1.4
| 
| ...is available at
| 
|   http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}

Good stuff, Manuel.  Thanks!

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/.   I'm unsure about
access permissions, but I'm copying Jeff Lewis who is root on
that machine.

=

More generally, the spec is looking good. 

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

* 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'.  

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

* "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 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?

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



RE: CCallable/CReturnable classes (was Re: FFI Report, CVS Id 1.5)

2001-06-13 Thread Simon Peyton-Jones

| Is CCallable/CReturnable a useful part of the new 
| multi-lingual ffi story (either in the ffi spec or in GHC's 
| implementation of the ffi spec)?

Definitely not.  It's a GHC implementation trick, that's all. Doesn't
belong in a spec

Simon

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



RE: FFI Report, CVS Id 1.5

2001-06-15 Thread Simon Peyton-Jones

| There is now a new revision of the definition at
| 
|   http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}

Great stuff.  It's looking good.

| > * 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).

I disagree with this.  Here's why.

I think it is useful to make a separation between
- what must be implemented by the Haskell compiler
- what is defined by a portable library

To implement a C interface, a Haskell compiler must implement
- foreign ccall ...
- the types: CInt ...etc
- Storable instances for those types

So I propose that we have

Section 4: External platforms

   4.1: C [ccall, stdcall]
   4.2: Java
   4.3: .NET

(i.e. lift current 3.5 to top level).   Furthermore, within each of
these I suggest
we define what foriegn types and instances must be defined.

Simon



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



RE: FFI Report, CVS Id 1.5

2001-06-15 Thread Simon Peyton-Jones

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


Now I didn't follow all the details of why this was a bad idea
but I thought I'd mention the problem.My preference would
be to specify "wuggle" as the package name in the C entity,
and attach a ".h" to it when emitting code for certain common
platforms.  The programmer would need to provide a suitable
.h file, if necessary simply by #including the ones really needed.

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

Simon

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



RE: FFI Report, CVS Id 1.5

2001-06-18 Thread Simon Peyton-Jones


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

OK: belt and braces.  Certainly the 'mylib' is properly part of foo's
external
name.  Let's use the "::" syntax which .NET uses for other namespace
management
things

"myheader.h mylib::foo" foo :: Int->Int

Simon

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



RE: Trying to build HDIRECT with ghc-5.00.2

2001-07-12 Thread Simon Peyton-Jones

| (*) - ghc-5.00.2 give Int.sizeofInt{8,...} the type Int32; 
| HDirect generated sources assume Word32 (as it should be). => 
| you may need to tweak the generated code in a select few 
| places to make ghc-5.00.2 happy.

Sigbjorn: 

Are you suggesting a change to the Int module?  It would
be nice to settle ethis so that no tweaking was reqd.

I'm ccing the FFI list as that seems the right place to decide.

Simon

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



RE: FFI Report, CVS Id 1.11

2001-08-23 Thread Simon Peyton-Jones

Manuel

Excellent stuff.  Truly excellent.  

Simon


* I have many small wording suggestions, but I'll just perform them
directly.

* Still uncontroversial, I found 3.2 to be in a funny order. I'll
re-organise it slightly.

* I found 4.1 pretty confusing, and I'm an unusually well-informed
reader.
  a) It was some while before I realised that the first entity
production is
only for foreign *import*.  The foreign *export* entity
production 
and its accompanying text is embedded in the middle of a vast
swathe
of foreign import stuff (both before and after!).   Let's have
sub-sections!

  b) Presumably an & import places constraints on the type?  Ah! That's
what
you mean by "static address", and later "imported address".
Easy to
be confused here.

Strong suggestion: give one example of each form in the
description-list.

  c) Explain that if there is no static/dynamic/wrapper, then static is
assumed.
Mention why "static" exists at all.  (To allow entities called
wrapper.)

* 5.4.2 Talks of "foreign export dynamic".  Out of date!

* 5.5  I think foreignPtrToPtr had better have an IO type, else you
don't quite know
when it'll be called,. relative to the touchForeignPtr...   Oh-ho!  It
doesn't matter!  
 If it hasn't been called then the supended call keeps the foreign ptr
alive.  If it 
has been called, the touch will keep the foreign ptr alive long enough.
Cunning. But worth explaining!

* 5.5 description of withForeignPtr.   Similarly, should explain a bit
about this "not safe"
stuff. What we mean is that the foreign ptr may be finalised afer
withForeignPtr is done, so the Ptr may be unusable after that -- unless
you touch the ForeignPtr afterwards, in which case it's ok Careful
explanation needed.

| > PtrDiff
| > ~~~
...
| Haskell already uses Int for these kinds of lengths: array
| indices are mapped to Int, default implementations of list 
| functions use Int for measuring lengths.
| 
| On 64-bit processors Int is 64-bit (or 63-bit when targeting
| OCaml etc.), so the need of handling objects larger than a 
| gigabyte in 32-bit architectures is temporary, if at all. 
...
| What about peekArray etc.? It's not clear where to stop.

I must say that I rather agree with Marcin here.  Let's just use Int
(but not Int32!). On machines with big address spaces, Ints will be big.
Keep it simple. Oh, and efficient!

| ForeignPtr
| ~~
| 
| Why do we still allow ForeignPtr as an argument to a foreign
| imported function, now that we have withForeignPtr?  Is it 
| just for convenience? If that's the case, it would be 
| enlightening for the spec to say so (perhaps in a footnote).

I agree with this.

C Calls
~
| 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? 

Makes sense to me, guv.  Makes the common case easy for Joe Programmer.

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

I agree with this.




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



RE: Type promotion in ccall arguments

2002-03-14 Thread Simon Peyton-Jones

| > I'd say it has all the information you need - you were 
| using it wrong.
| 
| That's fine - but I think the FFI specification should state 
| somewhere that the signature for a foreign import ccall 
| should correspond to the type of the C call *after the C 
| promotion rules have been applied*.

Strongly agree.  With at least one example for the benefit of
dense people likel mw.

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



FFI spec

2002-04-01 Thread Simon Peyton-Jones

Manuel

I've just had cause to look at the FFI spec.  Here's an idea.

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.  

Would that be OK?  If so, would you like to action it.  This is 
for clarity only -- no change to semantics.

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



RE: Problem with FFI?

2002-06-06 Thread Simon Peyton-Jones

Manuel:

Do you agree that something in the FFI spec needs to be fixed?
And hence is on your to-do list?

(Just wanting to be sure this one doesn't fall off the radar.)

Simon

| -Original Message-
| From: Alastair Reid [mailto:[EMAIL PROTECTED]] 
| Sent: 02 June 2002 18:03
| To: John Meacham
| Cc: [EMAIL PROTECTED]
| Subject: Re: Problem with FFI?
| 
| 
| 
| [reply redirected to [EMAIL PROTECTED]]
| 
| John Meacham <[EMAIL PROTECTED]> writes:
| > I may be missing something obvious here, but from the 
| current FFI spec 
| > it appears that it is impossible to create libraries in 
| haskell which 
| > are meant to be called from c code without running into undefined 
| > behavior. The problem is in the definition of hs_init() and 
| hs_exit() 
| > .  now, it is acceptable to have hs_init and hs_exit called in the 
| > initialization and finalization of your library, but the problem 
| > arrises when you link against more than one library which is 
| > implemented in haskell, suddenly whichever library is initialized 
| > secondly segfaults! (or whatever undefined behaviour means.).  
| > programs could suddenly stop working when a library is 
| changed from a 
| > c implementation to a haskell one, which seems to be a bad thing.
| 
| Hmmm, I see what you mean.
| 
| > proposed fix: allow nested calls to hs_init, hs_exit, a counter is 
| > incremented when hs_init is called more than once, and 
| decremented on 
| > hs_exit. only the last call to hs_exit will actually do 
| whatever needs 
| > to be done.
| 
| The hs_init function takes arguments - what if each call to 
| hs_init specifies a different set of arguments?  How about:
| 
|   hs_set_hs_argv   (int argc, char *argv[]);
|   hs_set_prog_argv (int argc, char *argv[]);
|   hs_init ();
|   hs_exit ();
|   
| Where:
| 
| hs_set_hs_argv sets command line parameters for the Haskell 
|   runtime system 
| 
|   It can be called at most once and that call must be before the 
|   first call to hs_init
| 
|   Warning! The flags are not remotely portable between different
|   Haskell runtimes.
| 
| hs_set_prog_argv sets arguments seen by getProgName and getArgs
| 
|   It can be called at most once and that call must be before the 
|   first call to hs_init
| 
| hs_init initializes the Haskell runtime
| 
|   It can be called multiple times and must be called before the first
|   call to any function exported by the Haskell code.
| 
| hs_exit finalizes the Haskell runtime
| 
|   hs_init and hs_exit are required to satisfy the usual 
| bracketing rules:
| 
|   1) At any time, the number of calls that have been made to 
| hs_exit must be
|  no more than the number of calls that have been made to hs_init.
| 
|   2) If the number of calls to hs_exit is equal to the number of calls
|  to hs_init, then no further calls to hs_init may be made.
| 
| 
| By the way, the name 'hs_exit' is a little confusing - I 
| expected it to have an ExitCode argument.  'hs_fini' would 
| better match its actual purpose.
| 
| > note that this cannot be implemented by the programmer 
| himself since 
| > there might be several third party libraries also implemented in 
| > haskell which an app wishes to link against.
| 
| You can implement the modified API (or your modified 
| semantics) quite readily as a little library which you link 
| against your program.  All you have to do is tweak the names 
| a little (e.g., s/hs/HS/) to avoid name clashes.
| 
| -- 
| Alastair Reid[EMAIL PROTECTED]
| http://www.cs.utah.edu/~reid/
| 
| 
| 
| 
| ___
| FFI mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/ffi
| 
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Library archives

2002-08-19 Thread Simon Peyton-Jones


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

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



RE: Proposed change to ForeignPtr

2002-09-11 Thread Simon Peyton-Jones

I confess that I have not followed the twists and turns of this
discussion, but it seems to have gotten more complicated than necessary.
There are several separate issues.

1.  Can a finaliser for a Haskell value be an arbitrary Haskell
computation?  For GHC, yes.  For Hugs, no (and for good reasons).So
Hugs can only allow a C procedure as a finaliser. 

2.  If a garbage collector (whether the Haskell gc or the Foogle gc)
finds that it is dropping a pointer to an object, when may it run the
finalizer?  Answer: it should be allowed to do so at any time: when the
pointer is dropped (for ref-count gc) or during gc (as Hugs does) or
after gc (as GHC does).

3.  If the finalizer, in turn, needs to call some kind of foreign 'free'
routine (e.g. the finaliser for a Haskell object encapsulating a Foogle
object calls the Foogle free code; or the finalizer for a Foogle object
encapsulating a Haskell value calls the Haskell free routine) it should
be allowed to do so at any time.   BUT DOING SO DOES NOT trigger an
immediate GC in the other system.  

Several people have explained why it would be bad to trigger immediate
GC. All the 'free' routine does is record that Foogle no longer holds
this pointer (or vice versa).  That information (as Alastair puts it)
tweaks local data structures (yes, there may need to be a lock if there
are separate OS threads involved), and that info is exploited at the
next GC.

4.  None of this says anything at all about asynchronous calls into
(say) Haskell from Foogle.  I don't understand what the issues are
exactly.

Simon

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



RE: Finalizers etcetera

2002-10-09 Thread Simon Peyton-Jones

| > (A mutex lock is required to ensure that the pending queue is not
| > traversed more than once, but that is all I think.)
| 
| I don't understand how this would work in single-threaded systems
(like
| I understand NHC to be).

I haven't been following the details of this discussion, but I think
there may be some confusion.

1.  I think we all now agree that it's easy to arrange to run finalisers
at the end of GC, not during GC, by putting them on a queue and running
them after GC.   But as recently as 27 Sept we didn't agree because when
Ross suggested that a Haskell finaliser could call a C function,
Alastair replied:
| That would have the garbage collector invoking a C function (this is
| ok) which then calls a Haskell function (this is not and the ffi spec
| says not to expect it to work).

Still, I think we now agree that this is fine.

2.  The end of GC is by definition a yield point in the original
program; that is, a point where it is prepared to do GC.

3.  Alastair's point is that a GC-yield point might not be a safe place
to run a finaliser.  His example is:
the main program maintains a list of active windows in a mutable
location
the finaliser removes an item from that list
He is absolutely right about this.

4.  I believe that the alternative Alastair advocates is to make
finalisers run in C only.  Why does that solve the problem?  Because
that would force the mutable list of windows (in the example) to be
implemented in C, and that in turn means that manipulating the list is
indivisible.


Conclusion: finalisers in C is simply a way of performing atomic
operations.


The obvious conclusions from this are as follows

a) Haskell finalisers are available on all systems

b) Finalisers can run at any GC point.  The programmer needs to be aware
of this.  Often it does not matter (e.g. calling 'free' to un-malloc
some space) but sometimes it does.

c) On systems (like Hugs and NHC) that have no synchronisation
primitives, you have to roll your own by calling C procedures.


I like this because it exposes what the real issue is without imposing a
single solution.  

Simon



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



RE: Finalizers etcetera

2002-10-09 Thread Simon Peyton-Jones

| > c) On systems (like Hugs and NHC) that have no synchronisation
| > primitives, you have to roll your own by calling C procedures.
| 
| Just to be clear about this.
| 
| You are not rolling your own synchronization primitive, you are
| writing code that is guaranteed to contain no preemption points
| because it does not call Haskell.

Yes, you're right. I should have said that.

Simon

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



RE: Finalizers etcetera

2002-10-09 Thread Simon Peyton-Jones

Alastair, 

You didn't respond to my proposal, perhaps because it didn't seem like
one
(I've changed a few words)

| a) Haskell finalisers should be available on all systems
| 
| b) Finalisers can run at any GC point.  The programmer needs to be
aware
| of this.  Often it does not matter (e.g. calling 'free' to un-malloc
| some space) but sometimes it does.
| 
| c) On systems (like Hugs and NHC) that have no way to builds
uninterruptible
| sequences, you have to roll your own by calling C procedures.

This is easy to specify and easy to implement.  It frees stuff promptly
(just after GC).  The down-side is that if you are careless you can
write stuff that mutates an IORef that is simultaneously mutated by a
finaliser.  In GHC you solve this with MVars.  In Hugs you solve this by
writing it in C.  But either way, full Haskell is available for
finalisers, and we have the nice simple interface that we all want.

I feel I must be missing something.

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



RE: Finalizers etcetera

2002-10-10 Thread Simon Peyton-Jones


| Am I right in thinking that you are proposing that we revert to
| writing Haskell finalizers but that Hugs and NHC programmers would
| have to avoid writing finalizers which manipulate Haskell state while
| GHC would use MVars to protect that state?

Yes, that's right.  It is often the case that there *is* no shared state
so a Haskell finalizer is fine.  But if there is, then there has to be
some
mechanism for atomic operations.  C is one such mechanism.

But there's something I'm puzzled about.  Hugs does support
non-pre-emptive concurrency, right?  (Where can I find a description of
it.)  So would it not be easy to implement (non-pre-emptive) MVars?  And
if they existed, everything would be fine, right?  We could just use
Haskell finalizers as we all want.  Or am I missing something.

(I'm assuming that the starting point for the entire discussion is
whether finalizers are written in Haskell or C.  Please let me know if I
missed something.)

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



RE: Finalizers etcetera

2002-10-11 Thread Simon Peyton-Jones


| I claim that the major thing that finalizers do is manipulate shared
| state. 

That is certainly true.  If they were pure, you'd never know they'd run!

| To get any benefit from writing finalizers in Haskell, I have to have
| MVars which protect against finalizers.  

Nearly right, but not quite.  You might write a Haskell finalizer that
did lots of useful things (e.g. consulted a large pure data structure)
before doing its state-mutation by calling C.

| > And if they existed, everything would be fine, right?  We could
| > just use Haskell finalizers as we all want.  Or am I missing
| > something.
| 
| Finalizers would have to be scheduled by the same scheduler as normal
| threads. 

Yes.

| The scheduler would need to prioritize finalizers over normal threads.

Desirable but not necessary.   The programmer cannot expect finalizers
to run promptly (there is always lots of literature on the GC mailing
list about this point).  

| Most of the cooperative concurrency implementation is written in
| Haskell.  That would have to be rewritten in C to make the operations
| atomic wrt garbage collection.

No, I disagree with this.  When GC runs, the finalizers can be put in
the ready queue.  After GC completes, the thread that was interrupted by
GC continues.  So a thread switch takes place ONLY when the thread
yields, as now.  (Again, promptness is not a reqt. If the thread never
yields, the finaliser will never run.  That is 100% ok. You absolutely
should not RELY on finalizers.



So the question before the house is to choose between:

A) Haskell finalizers: flexible; continue to be what we want when we
have concurrency; but if your impl does not support MVars you have to
call C to do state mutation.

B) C finalizers: less flexible; GHC will have (A) anyway; but arguably
one less trap for the unwary.


I still prefer (A), albeit not unto death, because
(i) I believe that supporting MVars in Hugs is not as hard as you think.
(I'm agnostic about NHC.)

(ii) Less incompatibility... (i.e. programs that use GHC extensions that
won't run on Hugs)

(iii) Moves in the direction we will ultimately want to go.  It seems
bizarre to write finalizers in a different language!


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



RE: Finalizers etcetera

2002-10-11 Thread Simon Peyton-Jones

| type MVar# s elt-- primitive
| 
| newMVar#:: State# s -> (# State# s, MVar# s elt #)
| takeMVar#   :: SynchVar# s elt -> State# s -> (# State# s, elt #)
| putMVar#:: SynchVar# s elt -> State# s -> State# s

Bad idea to look at the primops. The important things are
the MVar type
the operations newMVar, takeMVar, putMVar
the forkIO operation

Their semantics are described (completely I think) in my "Tackling the
awkward squad" tutorial.

| As another aside, in the hierarchical libraries docs (package base,
| Control.Concurrent.MVar) there appears to be an ambiguity:
| 
| readMVar :: MVar a -> IO a
| This is a combination of takeMVar and putMVar; ie. it takes the
| value from the MVar, puts it back, and also returns it.
| 
| It specifically avoids describing the combination as atomic, so I
| am uncertain whether the thread can be pre-empted between the 'take'
| and the 'put'?  Normally the answer would be yes, but then there is no
| benefit from having a separate 'readMVar' to combine the operations,
| so I am guessing that it /should/ be atomic.

False.   readMVar is completely described by
readMVar m = do { v <- takeMVar m; putMVar m v; return v }

If it gets pre-empted between the take and the put, no matter; anyone
trying to take from that same MVar will block.

Simon

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



RE: Finalizers etcetera

2002-10-11 Thread Simon Peyton-Jones

| (a) It was the first mention of MVars that I found in the docs.
| (b) I only really mentioned it because the type sigs are wrong.

Hmm.  That's not very clever.

| Doesn't it block if another thread manages to sneak a putMVar into
| the middle?  Maybe I should read your "Awkward Squad" paper to find
| out if this matters.

Yes it does block if another thread sneaks in a put.  If it matters,
you'd better code up a more robust abstraction (using MVars of course).

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



RE: Finali[zs]ers

2002-10-15 Thread Simon Peyton-Jones

John

I'm not quite sure what you mean.  I think you are saying that this is a
reason it's important to have Haskell finalizers, but I'm not sure.  How
would you like to write a paragraph or two to explain the issue, and we
can put it in the document?  That way it would say what you mean.  

Simon

| -Original Message-
| From: John Meacham [mailto:[EMAIL PROTECTED]]
| Sent: 14 October 2002 22:22
| To: [EMAIL PROTECTED]
| Subject: Re: Finali[zs]ers
| 
| I dont have cvs write access but you should mention something about
| expressing gc dependencies between ForeignPtr's. the only two ways to
do
| this in the current haskell systems are
| * weak pointers
| * touchForeignPtr from the finalizer of another ForeignPtr
| 
| if the second one is not allowed by restricting us to C only
finalizers,
| then the first needs to be added into the FFI, (or some other
mechanism
| invented). I consider this functionality vital for any non-trivial use
| of ForeignPtr, and it becomes more important as we move more stuff to
C
| land, as C structures become more common.
| 
| for more info on the use of this, see the FFI touchForeignPtr
| documentation and the paper describing Weak pointers in ghc. the fact
| that multiple people saw the need for this and came up with solutions
| probably says something about its usefulness.
|   John
| 
| On Mon, Oct 14, 2002 at 06:16:05PM +0100, Simon Marlow wrote:
| > > Thanks to everyone who has contributed to this discussion so
| > > far.  Since
| > > there are a lot of subtle points to be considered at once, I
| > > thought I'd
| > > try to write a summary of the issues raised so far.
| > >
| > > I'll put something in the repository so we can all hack on it.
| > > Hopefully I'll have something ready later today.
| >
| > oops, I should have mentioned that if you just want to read the
| > document, it will be available here:
| >
| >
| >
http://cvs.haskell.org/cgi-bin/cvsweb.cgi/haskell-report/ffi/finalizers.
| > txt
| >
| > just as soon as the CVS web server updates its repository.
| >
| > Cheers,
| > Simon
| >
| > ___
| > FFI mailing list
| > [EMAIL PROTECTED]
| > http://www.haskell.org/mailman/listinfo/ffi
| 
| --
|

---
| John Meacham - California Institute of Technology, Alum. -
[EMAIL PROTECTED]
|

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



RE: [Alastair Reid ] Re: cvs commit: haskell-report/ffi finalizers.txt

2002-10-15 Thread Simon Peyton-Jones

Hi Alastair

| a comment on SimonM's finalizer document.  I decided to comment rather
| than edit since my comments require more than tweaking the odd word
| here and there.

I suggest you edit directly, striving, as Simon did, to be even-handed.

I do have one comment on your rejoinders, though:

|   I don't see how adding concurrency strengthens the argument for
|   Haskell finalizers.
| 
|   Adding mutable Haskell state doesn't seem to strengthen it either.
|   Indeed, I assume the existence of mutable Haskell state in arguing
|   against Haskell finalizers.

Here I disagree!  If you have a concurrent Haskell program, with mutable
state and MVars and all, it's entirely likely that you'll have mutable
state that reflects the state of the external (e.g. C) world.  For
example, the GHC I/O library has Haskell I/O handles that reflect the
state of the underlying C handle.  (For example, they contain some
buffered characters as well as a C pointer to the underlying C object.)
So the finaliser actually watches to the *Haskell* object; when it
becomes unreachable the finaliser should run, and (amongst other things)
call a suitable finaliser on the C object.  But without access to the
Haskell world, the finaliser can't even get hold of the C pointer to
finalise!

So I believe that for a non-stateful, non-concurrent Haskell program the
case for Haskell finalizers is moot, it becomes much more compelling
once you have state and concurrency anyway.   Furthermore, Haskell
finalizers then behave just like threads (which by then exist anyway)
and must be treated with exactly the same care, no more and no less.


Incidentally, as I understand it, it is common ground that, by
scheduling finalizers on an ordinary Hugs thread, Hugs could provide
Haskell finalizers exactly as GHC does.  (Although that is not what
Simon's patch does, I know.)  The issue then becomes only one of
promptness, as Simon described in the writeup.  Am I right about that?

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



RE: [Alastair Reid ] Re: cvs commit: haskell-report/ffi finalizers.txt

2002-10-15 Thread Simon Peyton-Jones

When it comes down to it, I don't think we are that far apart.

1.  Everyone wants a C-finaliser interface; it's very convenient.  So it
should be in the spec.  It's probably a good plan to specify that such C
finalisers must obey the constraints of an 'unsafe' foreign import.

2.  It is clear that GHC at least will offer a Haskell-finaliser
interface, and that some people will use those Haskell finalisers; they
already do.   So it's desirable that they should be in the FFI spec so
that there's a standard for what they look like.

3.  We do not want the spec to require mutable state or concurrency, and
indeed Haskell finalisers make sense (albeit are much less convincing)
without such extensions.  Still, I think the spec should warn explicitly
that in the presence of mutable state care must be taken by the
programmer, because the finaliser can run at any time wrt the "main
program".

4.  The spec makes no guarantees about promptness.  Each implementation
may want to add notes about promptness.  For example, Hugs will say that
C finalisers will run much more promptly than Haskell finalisers (if it
supports the latter at all).


I think that the only real point of difference is that Alastair would
rather we did not even specify Haskell finalisers in the FFI spec,
because doing so encourages non-portability.  I don't agree about that;
I think people will use Haskell finalizers anyway, so we should specify
them.

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



RE: The Death of Finalizers

2002-10-22 Thread Simon Peyton-Jones
| In the meantime, I'm glad we have got a new function
|atomicModifyIORef
| which I for one will use, when it gets into GHC's regular release.

Just before this gets out of the door... any chance of calling it

modifyIORef

and documenting that it's atomic?  Sometimes names can get too long!

Not a big deal though.

Simon


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



RE: safe and threadsafe

2003-02-07 Thread Simon Peyton-Jones


| I have recently spent some time improving GHC's support for
| "threadsafe" foreign calls.
| As  a side effect of fixing a crashing bug, I made "safe" behave in
| exactly the same way as "threadsafe".

That's a positive advantage, provided there isn't a massive efficiency
cost.  I'm all for nuking 'threadsafe' if we can!

| 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? {In a SMP implementation,
| this might require additional interthread messaging}.
| What should happen when C code running in a separate OS thread calls a
| foreign exported
| function while the Haskell Runtime is blocked on a safe call?

Would all these questions go away if we made safe=threadsafe?

| Some people have said that "safe" calls are intended for serializing
| access to foreign libraries
| that are not multithread-safe. I think that MVars should be used for
| such purposes. Blocking the
| entire Haskell Runtime for the duration of a "safe" call is overkill,
| but it's not always enough:
| Many old C libraries keep state in global variables from one call to
| the next.

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.

Simon

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



Native threads

2003-02-07 Thread Simon Peyton-Jones
Folks

There was a spirited debate about the relationship between native OS
threads and Haskell threads.  I got very confused.  To clear up my
brain, Simon and I wrote a little operational semantics that tries to
make precise what is going on.  It's in CVS as
haskell-report/ffi/threads.tex

(Style files in haskell-report/styles)

I did send this round a couple of weeks ago, and others made a couple of
updates, but it seems to have killed the discussion stone dead!  

The (updated) postscript is at
http://research.microsoft.com/~simonpj/tmp/threads.ps

So I thought I'd mention it again.   Apart from anything else, it'd be
nice to get a merger of Wolfgang and Alastair's notes into the early
sections of the document.

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



RE: safe and threadsafe

2003-02-11 Thread Simon Peyton-Jones

| *) I am not convinced that thread synchronization should be done by
the
| FFI

Me neither!  It was news to me that anyone was *relying* on the
(implementation-specific) fact that a "safe" call blocks other Haskell
threads.  I'd always regarded "safe" as just like "threadsafe" except
that it was a bit more efficient, but with the penalty that blocking in
the foreign call could gum up all Haskell threads.

As Wolfgang says, the atomicity of "safe" is extremely dodgy.

I suppose that "unsafe" could also mean "guaranteed atomic".  After all,
it can't call in, nor do GC, etc.  And the RTS is in a state where
nothing else can execute anyway.  Even then, I agree with Wolfgang that
it's very smelly.

If you need atomicity, use an MVar, no?  You may not want two concurrent
GTK calls (although I don't see why not), but a GTK call concurrent with
some other I/O would be ok.  

If two threads are drawing in two different GTK windows, couldn't they
be concurrent?   

simon


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



RE: Bound Threads

2003-03-03 Thread Simon Peyton-Jones
[I've updated the "Semantics for foreign threads" document by
re-ordering the sections a bit.  It'd benefit from having a bit more
formal syntax.  No one has commented a single word on the operational
semantics.  I don't know whether that's because it's so clear that no
discussion is needed, or so opaque that no discussion is possible.]


| > I must admit that I can't remember the
| > exact semantic distinction between those "safe" and "threadsafe"
| 
| The problem is, nobody does... the original implementation didn't work
| in all cases. The original implementation made "safe" calls block all
| other haskell threads in some cases, and crashed in other cases.
| "Threadsafe" means that calling the foreign import shouldn't block or
| otherwise disturb other haskell threads. "Safe" means... well...
almost
| nobody seems to know, and still fewer people agree on it.
| In the current "HEAD", there is no difference between threadsafe and
| safe. If someone comes up with a clear specification of why and how
| "safe" should be different from threadsafe, things might change again.

Indeed, the semantics in the "semantics of bound threads" document makes
no distinction between "safe" and "threadsafe" either.

The original intention was this:

a threadsafe foreign call must not block Haskell threads, even
if
the foreign call blocks in foreign land.

a safe call is not required to obey this constraint

The motivation was that thread-safety might require more admin (e.g.
relinquishing the lock on the main Haskell heap), and this admin might
be costly.

A side consequence of GHC's implementation (albeit not of the above
specification) is that no Haskell threads progress during a safe call
(unless it provokes a call-back..?).  I recall that some people actually
started to rely on this, though it was never intended as part of the
spec.


I think Wolfgang is saying that the apparent efficiency gain of not
requiring thread-safety is illusory, and so we can abolish the
safe/threadsafe distinction.   I think that would be a very worthwhile
gain.

Does anyone disagree with this? 

Simon

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


RE: Bound Threads

2003-03-07 Thread Simon Peyton-Jones
| First let me outline my current understanding of what 'bound' means.
| Consider the following scenario:
| 
|   Haskell program is running in OS thread 't1'
|   Haskell program calls C function 'foo'.
|   'foo' forks a new OS thread 't2'.
|   In parallel: 't1' calls Haskell function 'f1' and
|'t2' calls Haskell function 'f2'
|   'f1' calls C function 'g1'
|   'f2' calls C function 'g2'
| 
| My understanding is that 'bound' requires that 'g1' be executed by
| thread 't1' and that 'g2' be executed by thread 't2'.

You didn't say where the program mentions 'bound'!  

I tried very hard to give a precise description of what bound threads
are, in haskell-report/ffi/threads.tex.  (Wolfgang circulated a PDF
recently.)   Does that specification make sense?  Does it answer your
question?   (If not, we should improve it.)  

I'm sure it would be improved by examples -- would you like to add one?

Simon


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


RE: Bound Threads

2003-03-17 Thread Simon Peyton-Jones


| Maybe, the forkOS/forkIO approach is flawed, but I think we 
| should only rule it out when we can provide a convincing 
| example where only the keyword approach would work, and where 
| we can't use combinators to achieve the same effect.


Daan,

There has been extended discussion on this stuff, which Wolfgang and
Simon and I tried to boil out into a document.  It's hard to say exactly
what 'safe' or 'bound' exports, or whatever, might mean, so we give a
little operational semantics.

My hope is that the very same operational-semantic framework would serve
to describe your system. Would you like to write its transition rules,
in the same style?  Then we could compare the two more easily.   Without
that, I am hard pressed to understand the implications of what you
suggest, just as I was hard pressed to understand Wolfgang's proposal
till we had it specified.

You can find the document in the CVS respository in
haskell-report/ffi/threads.tex

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


RE: Bound Threads

2003-03-17 Thread Simon Peyton-Jones
| Now, what I don't like about my proposal and your proposal is 
| that the user has to be aware of OS threads when making 
| foreign calls by wrapping it in "threadSafe" or adding 
| "threadsafe" sometimes -- but maybe that is unavoidable.

Actually, the proposal currently on the table, which no one has objected
to, is

* abolish the distinction between "safe" and "threadsafe"
* make "safe" the default (it already is)

So the user needs to do something special only if she wants to
do something unsafe (by adding "unsafe" to the foreign import).

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


RE: Bound Threads

2003-03-21 Thread Simon Peyton-Jones
Daan

I think everyone is keen to make progress on this bound-threads stuff.
You have an alternative idea which we are trying to understand.  Do you
plan to have a go at the operational semantics, as a way of explaining
it?  At the moment we're a bit stuck: no one wants to move on before we
have some kind of consensus, but you're the only one who can help us
understand your proposal.

Simon

| -Original Message-
| From: Simon Peyton-Jones [mailto:[EMAIL PROTECTED]
| Sent: 17 March 2003 22:06
| To: Daan Leijen; Wolfgang Thaller; [EMAIL PROTECTED]
| Subject: RE: Bound Threads
| 
| 
| 
| | Maybe, the forkOS/forkIO approach is flawed, but I think we
| | should only rule it out when we can provide a convincing
| | example where only the keyword approach would work, and where
| | we can't use combinators to achieve the same effect.
| 
| 
| Daan,
| 
| There has been extended discussion on this stuff, which Wolfgang and
| Simon and I tried to boil out into a document.  It's hard to say
exactly
| what 'safe' or 'bound' exports, or whatever, might mean, so we give a
| little operational semantics.
| 
| My hope is that the very same operational-semantic framework would
serve
| to describe your system. Would you like to write its transition rules,
| in the same style?  Then we could compare the two more easily.
Without
| that, I am hard pressed to understand the implications of what you
| suggest, just as I was hard pressed to understand Wolfgang's proposal
| till we had it specified.
| 
| You can find the document in the CVS respository in
| haskell-report/ffi/threads.tex
| 
| Simon

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


RE: Bound Threads

2003-03-21 Thread Simon Peyton-Jones

| However, my proposal is not anywhere fundamentally difficult -- in its
essence, I just
| propose to move the implementation of the thread allocation strategy
from the RTS/C
| code, to a Haskell library. This gives programmers both a low-level
interface for
| explicit access and a high-level interface as it is now.

It may well not be difficult, but nevertheless I am having difficulty
understanding it.  I'll have to wait till you have time to explain it.  

| What I mostly wanted to ensure is that people have really thought
about this carefully
| and that they could give strong reasons for choosing a particular
design over another.

The difficulty is that I can't give strong reasons for choosing X over Y
when I don't understand what Y is.  Next week is ok though.

Good luck with thesis writing!

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


RE: Bound Threads

2003-03-21 Thread Simon Peyton-Jones
| I think the essence of Daan's proposal was that the goals we hope to
| achieve using 'bound', 'threadsafe', and other ffi annotations could
| be achieved by adding a small amount of additional functionality
| and wrappers and that benefits of doing this are:

That all sounds splendid. If only I understood what the proposal
actually was.  (Precisely; I do have a vague understanding of it, but
it's a slippery topic.)

Simon



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


RE: FFI Help

2003-06-06 Thread Simon Peyton-Jones
Manuel

Would it be worth mentioning or amplifying this point in the FFI spec,
or perhaps in an accompanying Appendix/Commentary of examples and FAQs?
Else someone else is going to trip over it sooner rather than later.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Glynn
| Clements
| Sent: 04 June 2003 08:32
| To: Matthew Donadio
| Cc: [EMAIL PROTECTED]
| Subject: Re: FFI Help
| 
| 
| Matthew Donadio wrote:
| 
| > I am just starting to experiment with FFI, and am running into a
| > problem.  I was to create an FFI to the lgamma(3) found in many of
the
| > newer libm implementations.  My code follows the sig.
| >
| > The lgamma function works.  The gamma function core dumps (I am
using
| > ghc 5.04.3) on me.  gdb reports a SIGSEGV in signgam(), but I'm not
sure
| > why.  I believe that I need to use the monad because signgam is only
| > valid after lgamma returns.
| >
| > Does anyone have an idea what I am doing wrong?
| >
| > Thanks.
| >
| > --
| > Matthew Donadio <[EMAIL PROTECTED]>
| >
| > > module Gamma (gamma, lgamma) where
| >
| > > import System.IO.Unsafe
| >
| > > foreign import ccall "math.h lgamma"  lgammaC  :: Double -> IO
Double
| > > foreign import ccall "math.h signgam" signgamC :: IO Int
| 
| signgam is an "int" variable, but this assumes that it is a function
| of type "int signgam(void)".
| 
| Write a C wrapper "int get_signgam(void) { return signgam; }" and
| import that.
| 
| --
| Glynn Clements <[EMAIL PROTECTED]>



| Or alternatively, foreign import the address of the int and read it
| directly with 'peek'.
| 
| import Foreign
| ...
| foreign import ccall "math.h &signgam" signgamC :: Ptr Int32
| ...
| gammaIO :: Double -> IO Double
| gammaIO x = do lg <- lgammaC x
|s  <- peek signgamC
|return $ fromIntegral s * exp lg
| 
| 
| Regards,
|   Malcolm


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


FFI docs

2006-04-14 Thread Simon Peyton-Jones
Manuel

A couple of comments about the FFI spec.


I was trying to find out whether the automatic newtype unwrapping for
'foreign' declarations was part of the FFI spec.  I searched for
'newtype'.  Nothing.

Turns out that the *only* reference is in the sentence in 3.2:
"The argument types ati produced by fatype must be marshallable
foreign types; that is, each
ati is either (1) a basic foreign type or (2) a type synonym or renamed
datatype of a marshallable
foreign type."

This is very quiet!  The "renamed datatype" nomenclature is never used
in practice (only in the Haskell report), and in any case the sentence
is hard to unpick without an example or two.


Second point.  Consider
foreign import "dynamic" foo :: (Int -> IO Int) -> ...

I'm not sure whether (Int -> IO Int) is considered a "marshallable
foreign type", according to the defn in 3.2. 

I also found the separation of 4.1.3 from 3.2 quite hard to understand.
I was searching in 3.2 for "wrapper" and "dynamic" in vain!  I don't
have a good solution to this, except perhaps some explicit fwd refs, and
a clear explanation of the logic behind the structure of the document.


Since some aspects of the FFI spec may change slightly for Haskell',
this seemed like a good moment to mention these points.

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