RE: mistake in definition of CFile?

2005-01-25 Thread Simon Marlow
On 22 January 2005 23:53, John Meacham wrote:

 The FFI spec says (in section 6.2) that CFile represents the C type
 'FILE' and has Eq and Storable instances.
 
 Is this a mistake? FILE is opaque and AFAIK, you can't copy or
 compare its contents and expect it to work. I can think of two
 possible interpretations:
 
 * the table should say CFile is equivalant to 'FILE *'.
 * One is meant to use 'Ptr CFile' and no Eq or Storable instances
 should exist for CFile. (it is opaque)

The latter, I think.

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


RE: Haskell PPL bug fix

2004-10-15 Thread Simon Marlow
On 15 October 2004 10:25, Axel Simon wrote:

 for Simon M: conceptually it would be nicer if GHC uses it's private
 version of GMP.

Yes.  This has been discussed on the GHC User's list (recently I
believe).  Ideally we'd like to replace GMP with something else.

 Alternatively, GHC could just use malloc for
 allocating memory and a finalizer each time an Integer goes out of
 scope. Would that be too slow?

Yes, that would be too slow.

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


RE: Fail: loop from finalizers and stuff

2004-07-05 Thread Simon Marlow
On 04 July 2004 23:54, Sven Moritz Hallberg wrote:

 Dear Foreign Function Interface,
 
 why does a program like the following fail with a loop exception
 (using GHC 6.2 on MacOS X)?
 
 -snip-
 import Foreign
 
 main =
   do
   f   - mkFinPtr finalizer
   fp  - newForeignPtr f nullPtr
   putStrLn Hello World
 
 finalizer ptr = putStrLn (Finalize ++show ptr++.)
 
 foreign import ccall wrapper
   mkFinPtr :: (Ptr () - IO ()) - IO (FinalizerPtr ())
 -snap-

This is a FAQ, but you could be forgiven because the latest version of
the FAQ on the web site doesn't have this entry yet.  Here it is:

varlistentry
  termI can't get finalizers to work properly.  My program
  sometimes just prints
  literallt;lt;loopgt;gt;/literal./term
  
  listitem
paraChances are that your program is trying to write a
message to literalstdout/literal or
literalstderr/literal in the finalizer.  Handles have
finalizers themselves, and since finalizers don't keep other
finalized values alive, the literalstdout/literal and
literalstderr/literal Handles may be finalized before your
finalizer runs.  If this happens, your finalizer will block on
the handle, and probably end up receiving a
literalNonTermination/literal exception (which is printed
as literallt;lt;loopgt;gt;/literal)./para
  /listitem
/varlistentry

 Also, does the use of a wrapper import constitute a callback from C
 in the sense of the following statement?
 
   Whether a finalizer may call back into the Haskell system is
system
 dependent. Portable code may not rely on such callbacks.
 
 I.e. is the above code non-portable?

Yes.

 Why is the ForeignPtr interface constrained to finalizers that are
 FunPtrs at all? I want to touch a ForeignPtr from another's finalizer
 to satisfy a liveness dependency (as suggested in the spec). What is
 the best way to do this?

Good point.  That comment in the spec is left over from when we had
Haskell finalizers in the standard, and doesn't make sense any more.
(Manuel - are you keeping errata somewhere?  Or is someone else?)

Doing this is now non-portable because some Haskell systems don't
support calling back into Haskell from a finalizer.  If you're committed
to being non-portable, then the right way is to use the
Foreign.Concurrent interface instead of the wrapper trick you use above.

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


RE: atomicModifyIORef

2004-06-28 Thread Simon Marlow
On 25 June 2004 15:09, Daan Leijen wrote:

 Ok, I never thought of that. However, isn't it the case
 that I normally just want to get the old value back?
 In that case, the current interface is not so friendly.
 
 Is anyone using this function to get something else than the
 old/new value *and* where the computation is expensive?
 
 If not, maybe we should (also) provide a nicer interface?

I've no objection to providing simpler versions of the more general
interface - in fact I believe we discussed this when atomicModifyIORef
was introduced.  How about:

 atomicModifyIORef_ :: IORef a - (a - a) - IO a
 atomicModifyIORef_ r f = atomicModifyIORef r (\a - (f a, a))

If this turned out to be a common case that needs to be fast, then we
can implement it using a primitive in GHC.

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


RE: [Haskell] ANNOUNCING: The Haskell Bookstore

2004-06-25 Thread Simon Marlow
On 25 June 2004 11:30, Daan Leijen wrote:

 Is there anyone who knows why atomicModifyIORef has type:
 
   IORef a - (a - (a, b)) - IO b(1)
 
 Instead of:
 
   IORef a - (a - a) - IO a (2)
 
 
 It seems to me that returning the old value is always good
 enough right?  Here is an implementation of atomicModifyIORef
 with the current type in terms of a function proposedModifyIORef
 with type (2).
 
 atomicModifyIORef :: IORef a - (a - (a,b)) - IO b
 atomicModifyIORef ref f
= do old - proposedModifyIORef ref (fst . f)
 return (snd (f old))

Yes, but in your version you apply f to the old value twice, potentially
duplicating an expensive computation.

atomicModifyIORef isn't part of the FFI spec, BTW.

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


Calling convention for FinalizerPtr

2004-06-14 Thread Simon Marlow
Something came up on the GHC list which made me realise that a slight
clarification is needed in the FFI spec.  FinalizerPtr is defined as:

  type FinalizerPtr a = FunPtr (Ptr a - IO ())

However, there is no way to specify what the calling convention for a
FunPtr is.  The calling convention is specified by the foreign import
declaration when calling one:

  foreign import ccall dynamic foo ...

In the case of finalizers, the ForeignPtr implementation must pick a
calling convention to call the finalizer with.  In GHC, we pick ccall.
This means that you can only use finalizers which expect the ccall
calling convention, something that isn't specified in the FFI addendum,
or the documentation for newForeignPtr.

What's the right thing to do here?  The simple thing is just to document
the restriction, but that might be entirely wrong on systems that don't
support the ccall convention, for example.  So perhaps there is a
per-platform fixed calling convention for finalizers.

Perhaps a FunPtr should remember its calling convention?  But then what
is the calling convention for nullFunPtr, or the FunPtr returned by
castPtrToFunPtr?

Or perhaps we should have different versions of mkForeignPtr for each
calling convention?  That doesn't sound too attractive either.

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


RE: Extension to the FFI to allow macro expansions to be avoided

2004-04-16 Thread Simon Marlow
On 16 April 2004 11:33, Marcin 'Qrczak' Kowalczyk wrote:

 Perhaps we should differentiate by a calling convention between
 linking to a function directly and generating a source-level C call?
 
 The calling conventions we know would correspond to linking to them
 directly. They would perform the necessary magic to turn off macros
 when compiling via C, and they would not need a C compiler when
 compiling via assembler. There is no need for specifying a C header
 in this case. 
 
 Another calling convention would generate a function wrapper with
 proper argument types. It would need foreign type declarations and
 included headers. The wrapped calling convention in this case is of
 course irrelevant, so it's a calling convention rather than a
 separate flag. 

I wondered about that (while writing my last post) but it still seems
like a hefty price to pay for the small number of problematic cases we
have, and given that you can already write the C stubs by hand to get
the desired effect.  Hmm, perhaps this falls in to the category of
something we expect an external tool to do?

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


RE: Extension to the FFI to allow macro expansions to be avoided

2004-04-13 Thread Simon Marlow
 
 On Thu, Apr 08, 2004 at 10:18:24AM +0100, Alastair Reid wrote:
  Now that I understand the problem, my feeling is that the 
 problem is not with 
  curses but with GHC's compilation method.  GHC is using a 
 shortcut by 
  pretending that the ffi is for interfacing to cpp+C whereas 
 the ffi is quite 
  clear that it is for interfacing to C.  So, I think the 
 thing to do is fix 
  GHC.
 
 And Hugs too.  The issue isn't extending the FFI but implementing it
 more accurately and consistently.  As you point out, systems compiling
 via C have been extending the FFI to a function+macro 
 interface, which is
 incompatible with systems compiling to native code.  Having 
 been bitten by
 the same thing in the opposite direction (macros that work 
 with ffihugs
 or ghc -fvia-C don't work with ghc -fasm), I'd favour turning off the
 macro interface, preferably with #undef, at least by default.

Agreed.  Why is #undef to be preferred over adding parentheses around
the function name as Ian originally suggested?

Contrary to what I first thought, disabling the use of macros in FFI
calls should have no impact on GHC, so I'm happy to make this change.

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


RE: Extension to the FFI to allow macro expansions to be avoided

2004-04-09 Thread Simon Marlow
 
 Alastair Reid wrote:
  [...] where the decision to insert parens is decided by a 
 command-line flag. [...]
 
 I'm still not convinced that any change is really necessary, 
 but I'd really
 prefer a command-line flag over a change in the FFI syntax. 
 The latter will
 lead to much more portability trouble than the former.

Adding a flag is fine by me.

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


RE: Request: withArrayLength

2004-03-30 Thread Simon Marlow
 
 The suggestion wasn't to rename it, but to move it from base 
 to haskell98.
 
 Then you could add these functions without changing the 
 interface of any
 of the modules listed in the FFI Addendum.

That would amount to saying that 'Foreign' isn't a hierarchical library
any more, and anyone wishing to use purely hirerarchical libraries in
their code should avoid it.

On one hand, this looks reasonable: Foreign already doesn't re-export
Foreign.C.  However, I do use it all the time.  So if we ever decided to
allow disabling of the haskell98 package, lots of supposedly
purely-hierarchical code would break.  Ho hum.

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


RE: Request: withArrayLength

2004-03-24 Thread Simon Marlow
 
 I think adding new (hierarchical) modules is the way to go for now.
 
 1) Hierarchical because it lets us use some nice clear
module naming style like:
 
  Foreign.NonStd.*
or
  Foreign.Extension.*
 
[I favour the former since the status of the lib is clearer.]

Not wanting to throw a spanner in the works, but we did agree not to use
these kinds of names back in the early days of the hierarhcical
libraries.  The general rule is to base names on the functionality
provided by the libraries only.

There are a few cases where we break the rules at the moment:
System.Posix and System.Win32 are a bit dubious, and there's
Unstable.Control.Monad.  But on the whole we're sticking to the policy,
and there are good reasons for doing so, so I vote not to introduce
Foreign.NonStd.

I'm beginning to think we should implement package versioning ASAP.  We
would need support for it in all compilers, though.

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


RE: Request: withArrayLength

2004-03-23 Thread Simon Marlow
 
 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?

We certainly want to be able to add new stuff to the FFI over time.
There are several ways we might do this:

  (1) Just extend the existing interfaces (don't change semantics
  of existing functions, though).

  (2) Add new modules only (not re-exported by Foreign)

  (3) Add new stuff to the hierarchical Foreign.XXX modules, but
  not the non-hierarchical variants (and Foreign keeps the
  same interface as the FFI spec).

  (4) Wait until we have versioned packages, and have separate 
  ffi-1.0 and ffi-1.1 packages.

I like (4) the best, but we can't do that yet - we know how to, but
there's a fair bit of work to get there.  Of the other options, I'm
tempted by (1).  (2) is unattractive because some of the new interfaces
will morally belong in existing modules (eg. withArrayLength clearly
belongs in Foreign.Marshal.Array).  (3) is unattractive because the
Foreign module overlaps, so we can't keep the hierarchical and
non-hierarchical versions separate.  (1) is unattractive because it
might break code that works with the FFI 1.0 spec (unlikely, though).

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


RE: How to force finalization of ForeignPtr

2003-12-22 Thread Simon Marlow
[ forwarded to [EMAIL PROTECTED] ]

In the current implementation there is no way to
 force finalization of the foreign ptr if there are 
 still references to it. In this scenario
 the finalization will be executed during the next 
 garbage collection. In some cases it is known that the
 foreign pointer value is not used anymore but the
 references still exist in the stack and they cannot be
 freed from the collector. In such cases I want to be
 able to explicitly finalize the foreign pointers. For
 that reason I wrote the following simple function:
 
 module FinalizeForeignPtr(finalizeForeignPtr) where
 
 import GHC.ForeignPtr
 import Data.IORef
 
 finalizeForeignPtr :: ForeignPtr a - IO ()
 finalizeForeignPtr foreignPtr = do
   finalizers - readIORef refFinalizers
   sequence_ finalizers
   writeIORef refFinalizers []
   where
   refFinalizers = case foreignPtr of
   (ForeignPtr _ ref) - ref
   (MallocPtr  _ ref) - ref

There's a race condition between multiple finalizeForeignPtrs, but apart
from that it looks fine.

I don't see any reason why we shouldn't have this.  GHC's weak pointer
interface has a similar function for running the finalizer early.

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


RE: H98 FFI Addendum 1.0, Release Candidate 15

2003-11-14 Thread Simon Marlow
 
 On Fri, Nov 14, 2003 at 01:57:41PM +1100, Manuel M T 
 Chakravarty wrote:
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?
 
 I don't think we need to say anything special, the conversion 
 to wchar_t
 * is just as defined as that to char *. it is a locale dependent
 operation just like withCString and friends. one would make their
 decision as to which to use based on the library they are 
 trying to bind
 too, if a wchar_t interface is supported it should be prefered because
 it is more likely to preserve character codes.

It is true that strictly speaking we don't need to say anything here.
But I think it would be helpful to include a footnote as a guide to
implementors, something along the lines of

   [1] Note that if the platform defines __STDC_ISO_10646__ then wchar_t
   characters are Unicode code points, and thus the conversion between
   Haskell Char and CWChar is a simple cast.  On other platforms, the
   translation is locale-dependent just as for CChar.

And the paragraph in question could be just

  The module \code{CString} also exports a
  variant of the above string marshalling routines for wide
  characters, i.e. the C \code{wchar_t} type[1].

Cheers,
Simon

___
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 Simon Marlow
 
 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.

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.

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


RE: Errors from Haskell, C/C++ Objects Linkage

2003-09-03 Thread Simon Marlow
 
 When linking a program with Haskell Code (also the main program),
 and interfacing to C functions (a lib*.a C++ application 
 library is also combined),
 the following error occurs:
 
 c:/ghc/ghc-6.0/libHSrts.a(Main.o)(.text+0x86):Main.c: 
 undefined reference to
 `__stginit_Main'
 c:/ghc/ghc-6.0/libHSrts.a(Main.o)(.text+0x9b):Main.c: 
 undefined reference to
 `Main_zdmain_closure'
 
 In the contrary, the error does not occur when linking a few 
 functions to the Haskell Main only.

Could you describe in more detail exactly what you're doing?  We need to
know: 

 - what version of GHC
 - what platform
 - the exact command lines you used
 - if possible, a copy of the code so we can reproduce the problem

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


RE: CWString

2003-08-28 Thread Simon Marlow
 
 3) link against another library such as libunicode which provides its
 own classification routines (this could be done optionally at compile
 time...)

libunicode is no good, I tried it.  It only recognises Unicode
characters up to '\x'.

The only right way to do this, it seems, is to generate the tables from
UnicodeData.txt.  However, I'm prepared to live with the current
solution as long as we document its shortcomings.  After all, it does
the right thing on the majority of our installed base.

Cheers,
Simon

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


RE: CWString

2003-08-27 Thread Simon Marlow
 
   In our new implementation of Data.Char.isUpper and 
 friends, I made the
   simplifying assumption that Char==wchar_t==Unicode.  With 
 glibc, this
   appears to be valid as long as (a) you set LANG to 
 something other than
   C or POSIX, and (b) you call setlocale() first.
  
  The glibc Info file says:
  
  The wide character character set always is UCS4, at least on
  GNU systems.
 yes. with glibc, wchar_t is always unicode no matter what the locale.
 better yet, all ISO C implementations  define a handy C symbol to test
 for this. if __STDC_ISO_10646__ is defined then wchar_t is always
 unicode no matter what.

Sure, but as I've been saying, the implementation of glibc doesn't do
this.  In the C or POSIX locale, the ctype macros only recognise ASCII.
Try it:

#include wctype.h
#include stdio.h
#include locale.h

main() {
setlocale(LC_ALL,);
printf(%d\n, iswupper('A'));
printf(%d\n, iswupper(0x391)); // Greek capital alpha
printf(%d\n, iswupper(0x3B1)); // Greek small alpha
printf(%d\n, iswlower(0x391)); // Greek capital alpha
printf(%d\n, iswlower(0x3B1)); // Greek small alpha
}

$ LANG=en_GB ./a.out
1
1
0
0
1
$ LANG=C ./a.out
1
0
0
0
0

Should this be considered a bug in glibc?

Cheers,
Simon

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


RE: CWString

2003-08-27 Thread Simon Marlow
 
 hmm.. how odd. I would consider it a bug, I think. I don't have a copy
 of the ISO spec handy but will be sure to look up whether that is
 conforming... It is certainly a malfeature if it is not a bug...

I fired off a message to [EMAIL PROTECTED], we'll see what they have to
say.

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


RE: stdcall

2003-07-22 Thread Simon Marlow
 
 On Saturday 19 July 2003 12:51 am, Ross Paterson wrote:
  Could the meaning of stdcall be broadened to the standard calling
  convention for libraries on the native system, i.e. pascal on Win32
  (as now) and ccall on Unix?  It would save a lot of fuss 
 for interfaces
  to portable libraries.
 
 If I understand you correctly:
 
 1) Even on Win32, a function defined with type:
 
 rty foo(argtys)
 
should be called using stdcall.

I don't think that's true.  The default calling convention on Windows is
still ccall (known as __cdecl to the C compiler), it's just that
cross-DLL calls are normally done using the __stdcall calling
convention.

On Windows, functions in the C runtime are called using the __cdecl
calling convention.  I just tested this by checking the assembly
generated for calling malloc().

Although __stdcall is used more often than __cdecl for library calls on
Windows, it doesn't seem to be used exclusively (someone correct me if
I'm wrong).

So I'd say that specifying a default calling convention which maps to
stdcall on Windows and ccall on Unix is probably a bad idea.  You've
just got to know which one to use on Windows - this is the job for a
tool which checks the FFI decls against the prototypes.

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


RE: exercising the storage manager

2003-06-10 Thread Simon Marlow
 
 g'day everyone,
 
 I'm getting segv's from a program using the FFI (ghc5.0x) on 
 MacOS X only,
 i.e. not on Linux, my primary development platform.
 
 So... does anyone have any tips for showing up dodgy uses of 
 the FFI wrt
 memory handling? What settings for GHC's garbage collector 
 will create the
 most pathological situations?
 
 Also, I have some qualms about foreignPtrToPtr; by it's type, 
 it seems to
 be exactly what you want most of the time, but due to the if 
 this is the
 last reference, the finalizers may run caveat it almost always isn't.
 I note that it already has some warnings attached to it, but...

Most of the time you should be using 'withForeignPtr'.  I don't think
there can be any legitimate uses for foreignPtrToPtr unless there is a
touchForeignPtr that is guaranteed to happen later.  And that's a tricky
guarantee, because it involves reasoning about strictness.

Does anyone else think that foreignPtrToPtr should really be called
unsafeForeignPtrToPtr?

 - does anyone have a safe use for it that doesn't involve 
 touchForeignPtr?
 
 - can the FFI spec somehow group together all functions that 
   may introduce memory leaks or unsafety?

Unsafety is normally indicated with an 'unsafe' prefix on the function
name.  Memory leaks are a different matter - since malloc on its own can
introduce a memory leak, I'm not sure how you'd indicate that.

Cheers,
Simon

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


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

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

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

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


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

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

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

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

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

Cheers,
Simon

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


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

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

 We know that T must contain bottom.

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

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

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

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

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

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

Cheers,
Simon

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


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

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

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

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

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

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

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

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

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


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

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

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

  peek :: Storable a = Ptr a - IO a

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

Cheers,
Simon

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


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

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

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

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


RE: Allocation Marshalling Question (again)

2003-05-28 Thread Simon Marlow
 
 Judging by the silence that greeted my last posts re this a 
 couple of weeks
 ago I suspect this is of no interest to anyone but me :-(
 
 An extra couple of weeks cogitation on this hasn't really 
 changed MHO much
 (other than I'm no longer so pessimistic about the safety of 
 my + operator). 
 
 Seeing as the FFI seems to be close to finalization I thought I'd have
 another go. So excuse me if this seems half baked, but am I 
 the only one who
 thinks the type signatures of utilities like this..
  allocaBytes :: Int - (Ptr a - IO b) - IO b
 ..are rather inconvenient?
 
 Wouldn't..
  allocaBytes :: Int - (Ptr a - b) - b
 ..be more useful?

I haven't thought about this too hard, but it seems technically
difficult if not technically impossible.

In an implementation which uses a foreign call to malloc to implement
allocaBytes, then there has to be a reliable way to ensure that the
memory is deallocated later.  If we're not in the IO monad, then I can't
see how to do this.

Even in GHC where we use garbage collected memory instead of malloc, we
still make use of the IO monad to control the lifetime of the allocated
memory.

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


RE: ForeignPtr naming

2003-03-20 Thread Simon Marlow
  This is all fine, except that implementing finalizer ordering slows
  down ForeignPtrs quite a bit, in particular mallocForeignPtr takes a
  20% hit just allocating the IORef needed to store the list of
  finalizers.  Ideas for a better implementation are welcome.
 
 Having obviously optimized the hell out of mallocForeignPtr, it sounds
 like it's time to optimize the hell out of IORef. :-)
 
 Or, on the assumption that the slowdown comes from splitting what was
 a single object into 2 or even three separate objects, do what it
 takes to turn it back into a single object - i.e., put a mutable
 field directly in the MFP object.

 Best of all, do as CAML has done and add the machinery (and semantics
 changes) necessary so that whenever you have a tuple with a mutable
 field in it, GHC will implement it without adding an indirection
 through a separate IORef object.  Highly worthwhile and might possibly
 help with your MFP problem :-)

I already optimised away one level of indirection by using a strict
field and -funbox-strict-fields (standard practice when putting an IORef
in a constructor :-), but there is still a separate object for the
primitive mutable variable.  Folding this into the constructor is an
interesting idea - I'll muse on it.
 
  Anyway, this message is really about what names we should use for
  the old Haskell-finalizer versions of newForeignPtr and
  addForeignPtrFinalizer (and as such it doesn't have any bearing on
  the FFI spec 1.0).
 
 I'm rather taken by 'oldNewForeignPtr'.

That implies the functionality is deprecated, rather than just
non-portable, which is not the case at all.

  I'm assuming that we want to keep these functions in some form in
  GHC - where to put them is one issue; Foreign.ForeignPtr is a
  possibility (but not ForeignPtr), or GHC.ForeignPtr.
 
 I'd put them in GHC.ForeignPtr and make no other change in their name.

One vote for GHC.ForeignPtr then.  Any others?

 Easy for people to transition, easy for people to see non-portable
 code, probably little risk of collision with the ffi-mandated FunPtr
 versions.

On the subject of non-portability: the hierarchy is scattered with
non-portable libraries, because the decision was taken a while back not
to use the hierarchy to indicate portability, but to use it to guide
programmers towards *functionality*.  There are exceptions - eg. for
extensions which are likely to remain compiler-specific.  I don't think
Haskell finalizers are necessarily GHC-specific, so putting them under
GHC doesn't seem right in the long term.

Cheers,
Simon

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


RE: safe and threadsafe

2003-02-07 Thread Simon Marlow
 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.

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



RE: newForeignPtr

2003-02-03 Thread Simon Marlow
 For a summary of the discussion, see
 

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/haskell-report/ffi/finalizers.
txt

 However, only Hugs implements this part of the spec at the moment.

It will be implemented in GHC before the next major release.  I'm not
intentionally dragging my heels on this one, just haven't got around to
it yet :-)

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



RE: newForeignPtr

2003-02-03 Thread Simon Marlow
 Simon Marlow [EMAIL PROTECTED] writes:
 
   However, only Hugs implements this part of the spec at the moment.
  
  It will be implemented in GHC before the next major 
 release.  I'm not
  intentionally dragging my heels on this one, just haven't 
 got around to
  it yet :-)
 
 And of course the ghc-5.04 branch will keep the existing 
 (non-standard)
 signature, because there are no API changes permitted in 
 bug-fix releases.

That's right - the change will be in 5.06 (or 6.00), not in 5.04.3.

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



RE: Repeated hs_init()/hs_exit()

2003-01-29 Thread Simon Marlow
 Just out of curiosity, what would happen if hs_exit were a noop? if it
 left haskell initialized? I imagine there would be a space leak if you
 expected the rts's heap storage to be reclaimed, but is there any
 user-observable state which would cause programs to behave oddly? Just
 curious mainly, I don't advocate this as a solution.

hs_exit() has three main purposes in GHC:

 (1) it runs any remaining finalizers
 (2) it generates the stats output (eg. +RTS -sstderr)
 (3) it generates the profiling output

For (1), we're considering not running finalizers at all at exit time,
so that would cease to be a problem.  (2) and (3) aren't particularly
important - we'll probably do whatever is easiest for the time being,
which is to output the stats/profiling the first time and do nothing in
subsequent hs_exit()s.

An interesting question is whether we can return the RTS to its
completely uninitialised state, freeing all the dynamic memory it has
accumulated and so on.  There are two ways I can see to do this:

  - Reload the data pages of the executable/library from disk (on
demand,
of course).

  - Arrange it so we can do the de-initialisation ourselves.  The main
thing here is being able to revert all the CAFs that have been
evaluated - we already have some of the machinery to do this.

I don't think we'll tackle this in the short term, but it would be a
nice feature to have.

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



RE: Threaded RTS Patch

2003-01-27 Thread Simon Marlow
 I haven't read Hans Boehm's paper (but will try to get a
 copy once I am off this plane and have a decent Internet
 connection again).  While I understand the problems of
 running finalizers at program exit, I think the OS plus
 explicitly-called-clean-up-routine argument doesn't always
 work either.  An explicitly called clean up routine doesn't
 help when a program terminates abnormally.

Using exception handlers, you can catch most kinds of abnormal
terminations and call your cleanup routines.  The kinds that you can't
catch are:

  - heap overflow.  That's a difficiency that we should fix.

  - RTS internal errors.  It is unlikely that cleanup routines
will be able to run after a RTS internal error anyway.

  - Other termination conditions, none of which we would be
able to run finalizers under: signals/process kills, 
power failure, etc.

  - Deadlock, which should be handled by time-outs in any
robust system.

So I submit that under all reasonable error conditions it is possible to
ensure that cleanup routines get to run.  GHC uses this method to delete
its temporary files, BTW (and it's currently a bug that a heap overflow
in GHC will cause temporary files to be left lying around).

Admittedly, exceptions aren't properly a part of H98 + FFI.  But I think
we can agree that this is generally a direction that we should be moving
in; Hugs now has exception support that matches GHC's, and the
implementation cost isn't that high for other Haskell implementations.

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



RE: Proposal: Pooled memory management

2003-01-20 Thread Simon Marlow

 Manuel wrote:
  [...]
  * 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.
 
 That's OK and I understand your motivation. Let's finish v1.0 first.

I agree, but I don't have any problem with forking the spec at this
point.  The changes to the current 1.0 RC are going to be very small
from now on.

 In a nutshell: Let's include as many useful patterns in the 
 next FFI spec
 versions as possible! Otherwise we might talk the same 
 language without recognizing it...

So we might well ask what useful new functionality is provided by a
pool-style memory manager.

One feature is performance: compared to using malloc/free, a pool is
going to be much cheaper.  But I'd be interested to compare the
performance you get from using pools to GHC's implementation of
mallocForeignPtr, which also sidesteps malloc/free to get decent
performance.

Compared to mallocForeignPtr, there are some qualitative differences
which might make one or the other more convenient in some situations:

  - mallocForeignPtr provides garbage-collected storage.  No need
to free the storage later.

  - However, you do need to use withForeignPtr to get access to the
object.  This can be quite annoying.

So, assuming the performance is roughly the same (I'm guessing that
using pools may be slightly faster than mallocForeignPtr, but not
significantly), do people see any other compelling reasons to be using
pools?

GHC's runtime has an Arena abstraction which is an implementation of
pool-style memory management, and could be used to implement Pools, BTW.

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



RE: ForeignPtr query

2002-12-04 Thread Simon Marlow
 1. part of this BDD library uses ints (not pointers) to identify
 garbage-collectable objects. there's nothing in the FFI to 
 cope with this AFAICS. i could:
 
 - hack the library (but would prefer not to).
 
 - say the functions in question deal with Ptr CInt, and hope 
 sizeof(int)
 == sizeof(int *) on all platforms i need to run this on (yuk).
 
 - plead for a general stick this arbitrary (small) C object in an
 optimiser-impervious box  generalisation of ForeignPtr.

There was a proposal for such a thing kicking around recently, and I
think there's no real problems with it.  Although you're the first
person to come along with a real application, to my knowledge.

Please feel free to mail [EMAIL PROTECTED] and make a case, I'd say
there's a pretty good chance it'll get adopted.

 2. how do i import a function pointer under ghc5.02? in 5.04 i say:
 
 foreign import ccall bdd_reorder_stable_window3
   bdd_reorder_stable_window3 :: FunPtr (BDDManager - IO ())
 
 and that works (i.e. i can treat it like any other Haskell function).

5.02 had something called 'foreign label', which does the same thing.
Check the docs for details.

 3. i'd like to see some array marshalling code that copes 
 with lists of
 ForeignPtrs, such as:
 
 -- | Marshall a list of ForeignPtrs. Same structure as withArray0.
 withForeignArray0 :: Ptr a
 - [ForeignPtr a]
 - (Ptr (Ptr a) - IO b)
 - IO b
 withForeignArray0 marker vals f =
   allocaArray0 len
 (\ptr - do pokeArray0 marker ptr $ map foreignPtrToPtr vals
 res - f ptr
 mapM touchForeignPtr vals
 return res)
   where len = length vals

ITYM:

  withForeignArray0 fps io =
 withMany withForeignPtr fps $ \ps -
 withArray0 nullPtr ps io

 the problem is it isn't as usefully polymorphic as the corresponding
 withArray0 function (e.g. consider [(ForeignPtr a, ForeignPtr 
 a)]). ideas?

What type do you want for it?

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



RE: MVar interface [was: Re: ForeignPtr-related signatures]

2002-11-19 Thread Simon Marlow
 The current `modifyMVar`, though exception safe, is not 
 atomic in the
 same way that the proposed `atomicModifyMVar` would be.  Unless I
 misunderstand, during the execution of `modifyMVar`'s second 
 argument, the
 mvar is empty and could be filled by some other thread.  With
 `atomicModifyMVar`, the contents of the mvar are changed 
 atomically, based
 on the given (pure) function; no other thread can intervene.

This is true, but I've never come across an application for which
atomicModifyMVar is essential; the two main idioms for using MVars that
I know of are

 - each thread does take followed by put in strict sequence

 - the MVar is used as a 1-place channel, with some threads doing
   put and some (usually one) doing take.

So the fact that modifyMVar isn't atomic in the presence of another
thread doing a concurrent put doesn't usually matter, because there are
no such threads.  However, I agree that atomicModifyMVar does provide
functionality which doesn't currently exist.

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



RE: ForeignPtr-related signatures

2002-11-18 Thread Simon Marlow

 Just some small questions: Are we really going to change the 
 signatures of
 newForeignPtr and addForeignPtrFinalizer from those which GHC 
 has for ages
 to the new C finaliser only ones? Why don't we use other names and
 deprecate the old ones? And what are the plans in this area for GHC
 5.04.2?

GHC 5.04.2 won't adopt any library changes, as it's only a patchlevel
release (we don't make API changes between patchlevels, only major
releases).

I don't really mind too much what names we use, I'd be fine with keeping
the current names but changing the types if that's the concensus.

Also still unresolved is what to do about atomicModifyIORef and friends,
BTW.

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



RE: ForeignPtr-related signatures

2002-11-18 Thread Simon Marlow
 That's what I expected. Would it be possible to include the 
 new functions
 in 5.04.2? OK, that's an API change, too, but simple 
 additions are rather
 harmless. If we don't include this stuff now, there is no 
 useful common ForeignObj API for GHC/Hugs/NHC in the near future.

Ok, I suppose we could bend the rules a little in this case, as long as
we don't change the behaviour of any existing functions.

  [...] Also still unresolved is what to do about 
 atomicModifyIORef and
  friends, BTW.
 
 I remember atomicModifyIORef, but what are its friends 
 exactly? PVars
 have died, IIRC, and some cunning constraints on the 
 execution order of
 finalizers were rejected, too.

There was this, from Dean Herrington:

  http://haskell.cs.yale.edu/pipermail/ffi/2002-October/000940.html

I don't have any strong feelings (I rarely do, where names are
concerned).

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



RE: ForeignPtr-related signatures

2002-11-18 Thread Simon Marlow
 Simon Marlow wrote:
  [...] There was this, from Dean Herrington:
 
http://haskell.cs.yale.edu/pipermail/ffi/2002-October/000940.html
 
  I don't have any strong feelings (I rarely do, where names are
  concerned).
 
 I would be happy with his proposal. We can leave the IORef 
 stuff in IOExts
 as it is and use the new signatures and functions in 
 Data.IORef. The only
 annoying thing is the signature of Data.IORef.modifyIORef, 
 but we could
 declare the old signature as a bug...  :-]

Actually, looking at the proposal again, I don't think I like the
changes to the MVar interface.  atomicModifyMVar seems strange, because
modifyMVar is already atomic.  We have to be careful about trying to
smooth over differences between IORef and MVar where those differences
are real and important.

I don't mind changing modifyIORef to have a signature which is more
similar to modifyMVar, and I think adding atomicModifyIORef_ is a good
idea (although it needs a new primitive if we're to take advantage of
its efficiency over atomicModifyIORef).  Summary:

 - make modifyIORef's type match modifyMVar
 - add modifyIORef_
 - add atomicModifyIORef and atomicModifyIORef_

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



RE: ForeignPtr

2002-11-07 Thread Simon Marlow
 Ah, got you.
 
 How about making ForeignPtr slightly more polymorphic so that 
 instead of
 working only on 'Ptr a' it works on 'a'.
 
 e.g., We'd have:
 
   newForeignPtr :: a - Finalizer a - IO ForeignThing a

Hmm, interesting.  This allows the implementation to divorce the object
you're interested in finalizing from the object which the finalizer
actually watches.  eg.

  data ForeignThing a = ForeignThing a X

where X is some object with identity, i.e. an object which is only
explicitly allocated in the IO monad.  Examples are IORef, MVar,
ForeignPtr - it doesn't really matter, as long as you can attach a
finalizer to it and it can't be arbitrary duplicated by the compiler.  

In GHC, this means we could get rid of the ForeignObj# primitive type.

If you want finalizer ordering, as discussed previously, the
implementation would have to be

  data ForeignThing a = ForeignThing a !(IORef [Finalizer a])

(the IORef has identity, so that serves as our X).

 obviously, we'd want to remove the word 'Ptr' from the name 
 of the type.
 Candidates:
 
   ForeignProxy, ForeignObj, Foreign
 
 I think 'Foreign' is an essential part (at least, given the
 restriction to C finalizers) and I favour the first two over the last
 which seems too general.

Maybe Finalized?

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



RE: ForeignPtr

2002-11-07 Thread Simon Marlow

 That was Ashley's original proposal, but SimonM responded in
 

http://www.haskell.org/pipermail/glasgow-haskell-users/2001-September/00
2290.html

http://www.haskell.org/pipermail/glasgow-haskell-users/2001-September/00
2304.html

I think I had the wrong end of the stick; or at least I hadn't
appreciated the extreme cleverness of the idea.  I think I've got it
now, though ;-)

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



RE: location of HsFFI.h?

2002-10-30 Thread Simon Marlow
 I was wondering whether there was any standard way to find HsFFI.h? I
 can hardcode it into my makefiles for my own projects, but when i
 distribute code, I end up having to add -I lines for every possible
 location of it, usually multiplied by every compiler version 
 it supports
 since that is often also in the path name. (and no, hmake is 
 not really
 an option. pure make is my tool). perhaps some option to the haskell
 compiler which spits out the appropriate flags to pass to the C
 compiler.

If you're using GHC, the trick is to use GHC to compile your C code too
because it adds the appropriate -I flag to the gcc command line.

If this isn't possible, then you can extract the information from the
output of 'ghc -v'.  The relevant directory is in the include_dirs field
of the rts package.

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



RE: location of HsFFI.h?

2002-10-30 Thread Simon Marlow
 On Wed, Oct 30, 2002 at 09:12:01AM -, Simon Marlow wrote:
  If this isn't possible, then you can extract the 
 information from the
  output of 'ghc -v'.  The relevant directory is in the 
 include_dirs field
  of the rts package.
   
   michaelw@stargate:~$ ghc --print-libdir
   /usr/lib/ghc-5.04.2
   michaelw@stargate:~$

Thanks, I forgot I'd added that flag :-)

 so:
 
   GHC_INCLUDES := $(shell ghc --print-libdir)/include
 
 might help.

More correctly, the directory relative to $libdir is found by:

$ ghc-pkg --show-package rts --field include_dirs
  $libdir/include

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



RE: The Death of Finalizers

2002-10-22 Thread Simon Marlow

 Do we still have atomicModifyIORef?
 
 I don't know that there's that much point now that Haskell finalizers
 are gone.  I don't have a strong objection (esp. since it seems every
 implementation now has it) but it doesn't seem so necessary now.

It ought to be significantly faster than using MVars if you can get away
with it.  I haven't measured it though.

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



RE: The Death of Finalizers

2002-10-22 Thread Simon Marlow
 | 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.

It has a different type:

  atomicModifyIORef :: IORef a - (a - (a,b)) - IO b
  modifyIORef :: IORef a - (a - a) - IO ()

we could either
 
1. specify that modifyIORef is also atomic.  That is useful,
   because using an atomic version of modifyIORef would be
   faster than using atomicModifyIORef if you don't need a
   return value.  However, the atomic version of modifyIORef
   would be slower than the non-atomic version.

2. add atomicModifyIORef_, with the same signature as modifyIORef.

I don't really have strong feelings either way, but I think I'd be
slightly inclined towards (2) if anything.

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



RE: The Death of Finalizers

2002-10-22 Thread Simon Marlow
  It has a different type:
  
atomicModifyIORef :: IORef a - (a - (a,b)) - IO b
modifyIORef :: IORef a - (a - a) - IO ()
 
 It would break backwards compatability, but
 
   modifyIORef_ :: IORef a - (a - IO a) - IO ()
   modifyIORef :: IORef a - (a - IO (a, b)) - IO b
 
 (both specified atomic) would be consistent with the MVar names.

Did you really mean those types, and not the types I quoted?  That
implies unsafeInterleaveIO if they have to be atomic.

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



Finalizers: conclusion?

2002-10-21 Thread Simon Marlow

Ok, I'm sad to say that the problem we recently uncovered to do with
finalizers sharing values with the rest of the program essentially kills
off the possibility of doing Haskell finalizers in systems without
proper concurrency support.  I'm rather embarassed that I didn't notice
this before; sorry for wasting everyone's time :-(

Let's keep C finalizers for the FFI spec.  In GHC I imagine we'll
continue to offer Haskell finalizers as an extension, but I haven't
decided on an interface yet (suggestions welcome).

From now on I intend to keep track of a strict quota that prevents me
from writing more email than code :-)

Cheers,
Simon

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



RE: The Revenge of Finalizers

2002-10-17 Thread Simon Marlow

 There's another problem with Simon's patch I haven't been able to pin
 down: if you run the example, interrupt it at the right point and type
 another expression, the finalizers run, but the expression is lost.

I can get it to fail another way too:

  main = do
p - mallocBytes 64
newForeignPtr p (print x)
print x
   where
x = sum [1..1]

Can't believe I didn't realise this kind of thing might be a problem
before... guess I was too fixated on the other issues.  Anyway, it
really needs someone who is familiar with the Hugs backend to comment on
whether either of these problems are fixable or not.

This one I think you could trigger by using the
unsafePerformIO-C-Haskell sequence too.

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



RE: C Struct Field Access

2002-10-17 Thread Simon Marlow

 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?

I wrote some stuff on accessing C structs from Haskell recently which
might be useful:

  http://www.haskell.org/pipermail/ffi/2002-September/000720.html

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



RE: declaring C enum types

2002-10-17 Thread Simon Marlow


   - If not, then how should enum values be declared in the FFI?
  
  What you need to do is run a little autoconf-like program which
  constructs a program containing a suitable example, runs it 
 through a
  C compiler and tells you what's going on.
  
  hsc comes very close but I'm not certain if it does exactly what you
  need.  If not, compiling and running this program should tell you:
 
 Hmm, careful.  The C compiler is free to be clever, and use a 
 char if there are =256 elements in the enum, and short or 
 int otherwise.  You want to know the size of your particular 
 enum, not any random enum.

Yes.  The C99 spec says (sec. 6.7.2.1):

   [#4] Each  enumerated  type  shall  be  compatible  with  an
   integer type.  The choice of type is
   implementation-defined   but   shall   be   capable   of
   representing  the  values  of  all  the   members   of   the
   enumeration. [...]

If a C compiler can choose any integer type, then it seems to me that
mixing code from two C compilers on the same platform might not work.
Hmmm.

Anway, I think Alastair meant to say hsc2hs (not hsc), but you do
actually get the right answer doing it this way.  In hsc2hs if you say

(#type enum foo)

you'll get a Haskell type which corresponds to the actual type used by
the C compiler (provided hsc2hs is using the same C compiler as was used
to compile the library, presumably).

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



RE: The Revenge of Finalizers

2002-10-17 Thread Simon Marlow


 I'd hoped that blockFinalizers would be useful for defining other
 primitives but since it won't even work for GHC, I agree that PVar
 will meet most of our needs.  (An even simpler design might be to
 extend our IORef implementations with 'atomicallyModifyIORef'.)
 
 So, is this a design that we could agree on?  

I like it.  I'd vote for 'atomicModifyIORef' rather than a new PVar
type, though.

Cheers,
Simon

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



RE: Why I want Haskell finalizers

2002-10-17 Thread Simon Marlow


  No, that's only a partial (and indeed very incomplete) solution.  It
  relies on the Java GC knowing that that particular reference to the
  Haskell StablePtr is the only one that matters, and vice-versa for
  the Haskell GC.
 
 So you want StablePtrs to contain a reference count, a new function
 to increment the count and for freeStablePtr to decrement the count?
 
 We toyed with designs like that but always found other ways to achieve
 the same goal - but it's easy enough to do.
 
 A variant is for newStablePtr to look for an existing StablePtr to the
 same thing.  We avoided this design because of the semantic issues in
 testing Haskell pointers for equality but mostly to avoid imposing a
 lookup cost that we'd rarely benefit from.

GHC's StablePtr implementation does all this, BTW.  We were considering
removing it because of the overhead, though.

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



RE: The Revenge of Finalizers

2002-10-17 Thread Simon Marlow

  I don't know how to achieve the same goal with
  atomicModifyIORef.

 I do.  To modify ioRef1 and ioRef2 simultaneously, write
 
 atomicModifyIORef ioRef1 (\ contents1 - unsafePerformIO 
 ioRef2 (\ contents2 - blah blah))
 
 The actual modification will take place when the result or 
 contents of ioRef1 or ioRef2 get evaluated. 

I don't understand how this works.  Unless I'm missing something, you'll
see the contents of ioRef1 at the point at which the first
atomicModifyIORef takes place, but the contents of ioRef2 from the time
at which the unsafePerformIO is evaluated, which is some unspecified
time later.  

Also another modification might come along before the first
unsafePerformIO is evaluated, and it might see the new value of ioRef1
but the old value of ioRef2, if it doesn't evaluate the value of ioRef1
early enough.

Nevertheless, I believe that the addition of atomicModifyIORef will let
us write System.Random and Data.Dynamic in a safe way - both libraries
have only a single global IORef to worry about.

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



RE: The Revenge of Finalizers

2002-10-17 Thread Simon Marlow

 Simon Marlow wrote:
 [snip]
  Don't you run into a problem even if the two threads use the same
  ordering?  Suppose
  
- thread 1 does the atomicModifyIORef, and gets preempted before
  doing the seq
- thread 2 does its own atomicModifyIORef, and the seq.  Thread 2
  gets an inconsistent view of the IORefs.
 
 No.  At the time of the seq in thread 2, the thunk (call it Thunk 2)
 returned by the second atomicModifyIORef will refer to the 
 thunk (Thunk 1)
 put in there by the first atomicModifyIORef.  The seq will cause the
 unsafePerformIO from the second atomicModifyIORef to be 
 evaluated.  This
 will come to the if statement which will demand the value 
 of Thunk 1.
 This will in turn provoke the evaluation of Thunk1.  This will cause
 the action of thread 1's simpleToggle2 to be evaluated to completion.

Ok, so it relies crucially on the fact that the 'if' causes evaluation.
(you might have written it to be more lazy, so that the pair was
returned immediately without evaluating contents1 first, for example).

In that case, yes I agree it is horrible :)

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



RE: The Revenge of Finalizers

2002-10-15 Thread Simon Marlow

  Indeed, I very nearly implemented such a thing as part of the patch
  I sent out.  However, it didn't look trivial enough to implement so
  I backed off.  The blocked state needs to be saved  restored at
  various points: when starting a finalizer, when invoking a
  foreign-exported function, and when invoking an exception handler.
 
 I think it's fairly easy.  A sketch is something like:
   
   // primitive called from Haskell
   void blockFinalizer(Cell m, State world) {
 blocked += 1;
 eval(ap(m,world));
 blocked -= 1;
 runFinalizers();
   }

Does this run into problems with exceptions?

Also, this is a nested call to eval(), in a primitive, which can invoke
an IO action and therefore re-enter Haskell without going through
unsafePerformIO.  Is that safe?

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



RE: The Revenge of Finalizers

2002-10-15 Thread Simon Marlow

  Also, this is a nested call to eval(), in a primitive, which can
  invoke an IO action and therefore re-enter Haskell without going
  through unsafePerformIO.  Is that safe?
 
 Yes, I think so.  Most calls to IO actions from primitives are safe
 and I believe these ones are too.  (In some ways, its the rarity of
 race conditions, etc. biting you that disturbs me most about Haskell
 finalizers: it's hard to remember to do the right thing when the wrong
 thing happens so rarely.)

So, are we now claiming that my patch *is* safe?  (Never mind about
IORefs, I'm talking about the implementation itself).

Cheers,
Simon

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



RE: The Revenge of Finalizers

2002-10-14 Thread Simon Marlow


  However even if Haskell finalizers + MVars are impossible in NHC, I
  don't think Haskell finalizers + mutable state have to be.  For
  example another mutable variable we could have would be a PVar which
  is always full and has functions [snip]
 
  updatePVar (PVar ioRef) updateFn =
 do
[stop any new finalizers running]
a - readIORef ioRef
writeIORef (updateFn a)
[reenable finalizers]
return a
 
 Just for the record, I think that if we were to pursue this approach,
 then the right primitive to add is:
 
   -- |
   -- Execute argument atomically with respect to finalizers.
   -- Nested calls to blockFinalizers are allowed.
   --
   -- That is, while executing the argument, no finalizers will start
   -- to execute.
   -- (Finalizers that are already executing may continue to execute.)
   blockFinalizers :: IO a - IO a

Indeed, I very nearly implemented such a thing as part of the patch I
sent out.  However, it didn't look trivial enough to implement so I
backed off.   The blocked state needs to be saved  restored at
various points: when starting a finalizer, when invoking a
foreign-exported function, and when invoking an exception handler.

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



RE: Finalizers etcetera

2002-10-14 Thread Simon Marlow


 I guess the Hugs documentation should say that using unsafePerformIO
 to call C which calls Haskell should be avoided.

Yes it should, if such behaviour can lead to strange crashes!  Better
still would be to work out exactly what constraints are required on the
use of eval() from primitive operations, and make sure that all the
primitives comply.  Then we can be sure that Haskell finalizers will
work too.

 I think Haskell finalizers are
 different: virtually every finalizer which manipulates Haskell state
 will have race conditions.

This is a separate issue - which I'll wait till I've written the summary
to address.

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



RE: Finalizers etcetera

2002-10-12 Thread Simon Marlow

  What hasn't been required is for the various data structures to be
  in a consistent state at that point, and Haskell finalizers might
  trip over those if run after GC.  SimonM's patch ran them at a
  different point, though.
 
 It calls them in eval doesn't it?
 eval is called by nearly every primitive in Hugs.
 Most calls are benign since the calls are at the start of the primop
 before any data structures have been fiddled with.
 
 It's even possible that none have any problems.  All I'm saying that
 we will have to look over the code before we know if there is a
 problem (while others are claiming that there couldn't possibly be a
 problem).

Actually, I was claiming that if there's a problem there, then it's one
you already have.  The reasoning I used is just that eval() can call a
foreign function, which can re-enter Hugs.  My patch added no new code
paths (as I said before).

Perhaps there *are* problems with existing primitives which call eval(),
but you need to check those anyway.

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



RE: addForeignPtrFinalizer

2002-09-30 Thread Simon Marlow

  Then I'll reformulate my question as a patch. [...]
  Is there anything fundamentally wrong with this approach?
 
 I still maintain that getting this to work, testing it and,
 especially, maintaining it is a lot of work.

Isn't it worth a little effort?  Requiring finalizers to be foreign
functions is a serious wart in the FFI, especially when we're strongly
advocating that as much marshalling should be done in Haskell as
possible.

As for the testing and maintenance, you can see from the patch that the
changes are quite small and mostly obviously correct.  The only
difficult correctness property is whether it's ok to have eval() invoke
runIO() and thereby eval() recursively, but the reasoning is simple:
from eval() you can already call a foreign function, and foreign
functions can invoke foreign-exported Haskell functions, which in turn
re-enter eval() through runIO().  So the patch doesn't add any new
invariants.

You do have to worry about the impact of running Haskell finalizers at
any point during execution of Haskell code.  Since you can't do any
concurrency synchronisation between the finalizer and the main Haskell
thread, shared access to mutable data is impossible.  This is just
something you'd have to document carefully (note, it's not something you
can do with the current finalization mechanism either, but there it's
obvious).

 [For example, you
 mention that finalizers that point to the object they finalize don't
 work.  I guess we could fix that by adding GHC-style WeakPtrs.]

This isn't as big a problem as it sounds.  The finalizer can refer to
the Ptr, just not the ForeignPtr.  If it is essential to refer to the
ForeignPtr (I can't think of a reason why it should be), then we could
change the spec so that it was passed as an argument to the finalizer.

Cheers,
Simon

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.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: addForeignPtrFinalizer

2002-09-26 Thread Simon Marlow

  Actually in the current implementation the finalizers are not
  attached to the ForeignPtr at all: it's the other way around. 
 
 Ah, I see.
 
 Fortunately, I don't think my sketched implementation depended on such
 an attachment since it added an attachment of its own.  The design is
 intended to sit on top of the current GHC implementation (i.e., one
 with Haskell finalizers and no control over the order they are run).

Yes, you're right.  We could do it that way.  I'm also concerned about
adding the extra overhead though, especially if this is something that
will rarely be needed.  Are we sure this is what we want?

At least I can optimise mallocForeignPtr again and avoid registering the
finalizer until the first call to addForeignPtrFinalizer.

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



RE: addForeignPtrFinalizer

2002-09-25 Thread Simon Marlow

  I tell you what, I'll implement finalizer ordering if you 
 guys implement
  full Haskell finalizers :-)
 
 How about providing newForeignPtr as specified?  (Or are you 
 still hoping?)

Still hoping ;-)  The discussion seemed to stop without reaching a
conclusion last time.  At least, I still don't think I fully understand
why the current newForeignPtr is not implementable without concurrency,
given that a form of context switching must already exist in order to
implement foreign import that re-enters Haskell.

Anyway, it's not that big a deal.  I'll hopefully get round to making
the change soon.

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



RE: addForeignPtrFinalizer

2002-09-24 Thread Simon Marlow

 The spec says there are no guarantees on the order in which 
 the finalizers
 are run.  Doesn't this make this function almost impossible to use?
 Suppose one finalizer frees the storage and the other cleans 
 up something
 it refers to.  I'd suggest running the finalizers in the reverse order
 to the order they were added, i.e. the new finalizer will be 
 run before
 any existing ones.  Now that finalizers are FunPtrs, there should be
 fewer semantics problems.

Ordering of finalizers is not usually well-specified - I realise this
case is special (the finalizers are attached to the same object), but it
would still be quite tricky to implement in GHC.  The reason is that for
each finalizer we create a new, independent, weak pointer that points to
the target object.  (that's probably how we came to have
addForeignPtrFinalizer in the first place; it's a natural generalisation
in GHC, but perhaps not if you use a different implementation of
ForeignPtr. )

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



RE: lightweight struct handling in FFI?

2002-09-19 Thread Simon Marlow

 From: Antony Courtney [mailto:[EMAIL PROTECTED]] 
 
 While the FFI spec. is excellent, I'd really like to see a companion 
 document with real examples of how to use the FFI for the 
 easy, obvious 
 kinds of library interfacing tasks that are likely to arise 
 in practice.

There are quite a few examples in fptools/libraries in the CVS
repository.  These libraries all use the FFI: IO, Time, Directory,
CPUTime, Network.Socket, Text.Regex.Posix, and the new System.Posix
stuff.

I agree, it would be nice to have some introductory material on
programming the FFI for real, though.

 Such examples would hopefully help answer things like the following 
 rather naieve question that I have:
 
 Is there a particular best way to deal with C functions that take 
 lightweight struct values (or pointers to such structs), 

To answer your question, there are several choices, each with its own
advantages and disadvantages.  You'll find examples of these in the
libraries I mentioned above.  I'm assuming that you want to use the FFI
directly (possibly with help from c2hs or hsc2hs), rather than use one
of the higher level tools.

1. Fully marshal the structure to/from Haskell.

The best way to do this is to write a Haskell datatype for the
structure, and define a Storable instance for it.  You can use a tool to
help you write the Storable instance in a portable way: hsc2hs and c2hs
are good for this.

Full marshalling is likely to be a good choice when you want to do lots
of manipulation of the structure on the Haskell side.

2. Keep the structure in its C representation, and manipulate the
structure using peek/poke in Haskell.

This is a good choice if manipulation on the Haskell side is limited,
for example if a single field is required to be extracted, and you don't
want to marshal the entire struct into Haskell.  Also, sometimes the
representation is partially abstract on the C side (many C structs in
POSIX for example are only partially specified by the standard), so
fully marshalling it is not an option.

If the lifetime of the struct is well-known and scoped (such as across a
single call to a foreign function), then the MarshalAlloc.alloca family
of functions can be used to allocate it.  Again, to portably peek/poke
individual fields, you'll probably find that hsc2hs or c2hs are useful.

If the lifetime of the structure does not work well with alloca, or you
want it to be garbage collected, then use a ForeignPtr instead.  The new
functions mallocForeignPtr and mallocForeignPtrBytes provide for this
kind of allocation, and will perform better in GHC than using explicit
malloc/free.

Hope this helps,

Simon
___
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 Simon Marlow


   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.

... maybe I'm being stupid, but I don't see what the problem is.  Why
can't mallocForeignPtr be implemented as:

  mallocForeignPtrBytes size = do
r - c_malloc (fromIntegral size)
newForeignPtr r ptr_c_free

  foreign import ccall unsafe malloc
c_malloc :: CInt - Ptr a
  foreign import ccall unsafe free 
ptr_c_free :: ForeignPtr (Ptr a - IO ())

i.e. it's completely independent of MarshalAlloc.malloc.  If you happen
to know that MarshalAlloc.malloc is the same as C's malloc, then you
could use that instead, but you don't have to.

A separate issue is whether MarshalAlloc.malloc *should* be specified as
being an interface to C's malloc().  I hadn't noticed that it currently
wasn't.  I don't think I have any code that relies on it, and I can't
think of any strong arguments one way or the other, apart from the fact
that MarshalAlloc is not part of the C-specific marshalling library.

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



RE: Proposed change to ForeignPtr

2002-09-11 Thread Simon Marlow

I'm afraid George's questions have also rekindled my curiosity about
whether implementing Haskell finalizers is really as hard as it sounds.
Much has been written, but I still don't think we've got to the nub of
the issue.

On the face of it, if you can implement 'foreign import ccall safe',
then you have a re-entrant runtime system.  The times at which the
program can make one of these foreign calls are limited, i.e. in the IO
monad only - but I believe there's nothing particularly special about IO
computations in the evaluation models used by nhc98 and Hugs (correct me
if I'm wrong).

Alastair writes:

 The way GHC implements preemption is an optimized form of: set a bit
 when preemption is needed; and make sure that generated code will test
 that bit whenever it is in a position to perform a context switch.
 
 What you're asking Hugs and NHC to do is: add a function to a list
 whenever you have a finalizer to run; make sure the interpreter will
 test that bit whenever it is in a position to perform a context
 switch.  
 
 It's basically the same.  We don't have to mess around with signals to
 provide a regular timer interrupt but that's the easy bit of the code.

Ok so far.

 We can probably avoid messing around with multiple C stacks.  That's a
 significant saving but, it's the complexity of that is fairly
 self-contained - we could probably steal some code from some other
 language implementation.
 
 The cost is going over all data structures in the system making sure
 that operations on them are suitably atomic.  One of the issues I
 remember from old versions of GHC was that some of the primops would
 do some work, allocate some memory, then finish the job.  The classic
 error to make in that code was for the second half of the code to
 assume almost anything about what happened in the first half of the
 code: how much space is on the stack, does a table have free space in
 it, is this pointer into the middle of an object ok?

You certainly can't keep local variables live across a heap check,
everything has to be saved on the stack.  Hugs is different because it
has a conservative GC, so doesn't need to save everything on the stack
for a GC.  But how does it implement a safe foreign call?  Presumably it
must save away state on the stack in a way that the computation can be
resumed safely, and that's all you need in order to be able to run a
Haskell finalizer.

 The problem is the scope: every single data structure and every bit of
 code that accesses it has to be vetted and we have to keep it in mind
 as we maintain the code.  It's a high price to pay and I don't think
 it's necessary (because all you really need is for the runtime systems
 to talk to each other in very limited ways).

I don't quite understand this: could you give a concrete example of some
extra invariant that has to be maintained?  In GHC, context switches
happen at very precise points (i.e. heap checks) so I don't think we
have these kind of problems; certainly I don't remember vetting every
single data structure.  Can't Hugs use a similar approach?

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



RE: module Data.Bits

2002-09-10 Thread Simon Marlow


 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.

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.

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



RE: Cheap ForeignPtr allocation

2002-09-04 Thread Simon Marlow

  [...] using a ForeignPtr here, with free() as its finalizer, adds so
  much overhead that [...]
 
 Where is the overhead coming from?  Is it the cost of a C call or the
 cost of the standard malloc library?

It's the combined cost of

  - malloc()
  - creating a weak pointer to register the finalizer
  - running the finalizer
  - free()

I can't remember the exact break-down, but I believe more than half the
cost is in malloc+free.

 If the latter, I imagine that a
 custom allocator would have similar performance to using pinned
 objects.

Yes, using a custom allocator is likely to get you most of the benefit
(I say most, because you'd still need a finalizer and a free() routine,
compared to GC).  

But this is an argument in favour of the new interface, because it
abstracts away from the actual allocator used, so the implementor is
free to provide a custom allocator.  That's a win, isn't it?

 (I'm sort of assuming that pinned objects are more expensive
 than normal objects.)
 
 btw I don't know if it's relevant but there's an important semantic
 difference between allocating on the GHC heap and allocating on the C
 heap.  The C version can be manipulated by the malloc.h functions.  In
 particular, you can call realloc on it.  Do that on the GHC heap
 version and... well, it won't be pretty.  I don't know if this is
 relevant because using realloc with ForeignPtr'd memory is likely to
 be a delicate procedure no matter how it got allocated.

Yes, I thought about this.  Fortunately a ForeignPtr isn't mutable, even
using GHC extensions, so I can't see a way to safely call realloc() once
you've made a ForeignPtr.

Anyway, the docs for mallocForeignPtr would have to say something like
the pointer is not guarnateed to have been returned by malloc().

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



RE: Proposed change to ForeignPtr

2002-09-04 Thread Simon Marlow

 1) Add these functions:
 
  makeForeignPtr
:: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)
  attachForeignPtrFinalizer 
:: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO ()
 
It is implementation defined whether the free functions are allowed
to call Haskell functions.
 
 2) Remove newForeignPtr and addForeignPtrFinalizer
[GHC can go ahead and list them as non-standard extensions]
 
 
 There's a minor issue about whether the old function names should be
 reused (leaving GHC to come up with its own names) or not.  I have
 ceased to care either way.

I have a slight preference for re-using the old names, at least for
newForeignPtr.  The reason is that it follows the naming conventions in 

http://www.haskell.org/~simonmar/libraries/conventions.html

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



RE: Cheap ForeignPtr allocation

2002-09-03 Thread Simon Marlow

 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?

Uh, my memory's a bit vague too :-)

For a long time we were trying to get cheap allocation/freeing for
temporary storage, i.e. a cheap alloca.  We managed to achieve that when
I realised I could pull a trick with GHC's garbage collector and have
pinned objects as long as they don't contain any pointers into the
heap.  So instead of using malloc()/free() for alloca, we allocate a
pinned ByteArray# and let the GC free it.  (it needs to be pinned so
that it can be passed to foreign functions which might re-enter the RTS
and trigger GC, etc.)

This proposed extension to ForeignPtr is just taking the idea one step
further: we can use the same trick for ForeignPtrs too, at least in the
common case where you want the finalizer to free() the object again.

 Does this, then, effectively solve
 this old problem?  Wouldn't you want newXXX and withXXX
 variants of the above, too?

The two functions I mentioned are all that's needed:

   mallocForeignPtr  :: Storable a = IO (ForeignPtr a)
   mallocForeignPtrBytes :: Int - IO (ForeignPtr a)

they both do the job of a combined malloc/newForeignPtr.  withForeignPtr
still works fine with a ForeignPtr constructed this way.

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



RE: Cheap ForeignPtr allocation

2002-09-02 Thread Simon Marlow

 Can you achieve the same performance gain by adding some 
 rewrite rules?

Perhaps you could try to spot

(=) malloc (\p - newForeignPtr p free)

Hmmm.  Actually I'd like to do both: add the functions, because they
encapsulate a common case and guarantee a speed improvement if you use
them, and add the rewrite rule because it might catch some cases in
existing code.  The problem with relying on rewrite rules exclusively is
that they tend to be a bit fragile and can fail to trigger without you
noticing.

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



RE: Updates to FFI spec

2002-08-13 Thread Simon Marlow


 On 12-Aug-2002, Simon Marlow [EMAIL PROTECTED] wrote:
  
  I'd be equally happy (perhaps happier) if the header file spec was
  removed altogether.  In a sense, this would leave the 
 Haskell part of a
  foreign binding even more portable, because it doesn't have 
 to specify
  the names of header files which might change between platforms.
 
 This is a C interface we're talking about, right?
 
 In C, the name of the header file is part of the API.
 It doesn't change between different platforms unless
 the API changes.
 
 Specifying the header name is essential if Haskell 
 implementations are to
 ever apply any type-checking to these foreign interfaces.  If 
 they don't,
 then in practice I think Haskell programs using the FFI are 
 likely to be
 less portable, and certainly more error-prone, since they will contain
 type errors that may cause problems on one platform but not another.

Specifying the header name is also essential for certain implementations
(eg. GHC).  I wan't suggesting not supplying the header file at all,
just not supplying it in the foreign declaration and not defining it as
part of the standard.  But I take your point about the header file(s)
being a proper part of the API.

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



RE: Updates to FFI spec

2002-08-13 Thread Simon Marlow

  System.Mem.performGC does a major GC.  When would a partial GC be
  enough?
 
 I've described the image-processing example a bunch of times.
 
 We have an external resource (e.g., memory used to store images) which
 is somewhat abundant and cheap but not completely free (e.g.,
 eventually you start to swap).  It is used up at a different rate than
 the Haskell heap so Haskell GCs don't occur at the right times to keep
 the cost low and we want to trigger GCs ourselves.

Hmmm, the garbage collector is a black box and has its own complicated
heuristics for managing memory usage, but you are describing a mechanism
that depends rather heavily on certain assumed behaviours.  At the
least, that gives the garbage collector less flexibility to change its
own behaviour, lest it invalidate the assumptions made by the external
allocator.

 (In the image
 processing example, images were megabytes and an expression like (x +
 (y * mask)) would generate 2 intermediate images (several megabytes)
 while doing just 2 reductions in Haskell.)

I think I'd be tempted to try to use a more predictable allocation
scheme given the size of the objects involved.  Perhaps arenas? 

 How often and how hard should we GC?  We can't do a full GC too often,
 or we'll spend a lot of time GCing, destroy our cache and cause
 premature promotion of Haskell objects into the old generation which
 will make the GC behave poorly.  So if all we can do is a full GC,
 we'll GC rarely and use a lot of the external resource.
 
 Suppose we could collect just the allocation arena.  That would be
 much less expensive (time taken, effect on caches, confusion of object
 ages) but not always effective.  It would start out cheap and
 effective but more and more objects would slip into older generations
 and have to wait for a full GC.
 
 To achieve any desired tradeoff between GC cost and excess resource
 usage, we want a number of levels of GC: gc1, gc2, gc3, gc4, ...  Each
 one more effective than the last and each one more expensive than the
 last.  We'll use gc1 most often, gc2 less often, gc3 occasionally, gc4
 rarely, ...

But there seems to be no way to reasonably decide how often one should
call these.  Doesn't it depend on the garbage collector's own parameters
too?

  I think the spec should be clarified along these lines:
 
Header files have no impact on the semantics of a foreign call,
  and whether an implementation uses the header file or not is
  implementation-defined.  Some implementations may require a header
  file which supplies a correct prototype for the function in order to
  generate correct code.
 
 I still don't like the fact that compilers are free to ignore header
 files.  Labelling it an error instead of a change in semantics doesn't
 affect the fact that portability is compromised.

I don't see any alternative - would you require a compiler that has only
a native code generator to read header files?  When there's no C
compiler on the system? (this is realistic - at some point we'd like to
make the via-C route in GHC completely optional, so we can ship a
compiler on Windows that doesn't need to be bundled with GCC).

  Perhaps on GHC you should be required to register the top module
  in your program first, maybe something like
 
  registerModule(__stginit_Main);
 
  that way you can register multiple modules (which isn't possible at
  the moment, you have to have another module which imports all the
  others).
 
 What does that do?  Is it for threading, GC, profiling, ...?

Each module has a little initialisation fragment that calls all the
initialisation fragments for the modules it imports.

At the moment, there are two kinds of initialisation done for each
module:

  - each foreign export is registered as a stable pointer.  This
prevents the garbage collector from collecting any CAFs which
might be required (indirectly) by a foreign export.

  - when profiling, all the cost centres in the current module
are initialised.

It might be possible to do this using linker sets, but I haven't tried
(and it would probably be highly non-portable too).

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



RE: Updates to FFI spec

2002-08-13 Thread Simon Marlow

  At the moment, there are two kinds of initialisation done for each
  module:
 
 Both ELF and DLLs on Windows provide a way of specifying initializers.
 
 Or, easier yet, since the user is already using the hs_init function,
 you could use that.  The way you'd do that in ELF is to define a
 special section 'hs_initializers'.  Every module would contain a
 single object in that section: the address of the initializer.  (In
 gcc you do this by attaching an attribute to the variable.  In asm it
 is even easier since assemblers directly expose sections to the
 programmer.)  The linker will do what it does with all sections:
 concatenate the pieces from all object files.  hs_init would treat the
 section as an array of function pointers.  I'm sure that the Windows
 linker must have a similar mechanism - the main trick is figuring out
 what name to give the sections.

That's what I meant by a linker set :-)

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



RE: Library archives

2002-08-12 Thread Simon Marlow


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

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.

BTW I didn't know the spec was in CVS somewhere... where exactly?

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



RE: Proposed change to ForeignPtr

2002-08-12 Thread Simon Marlow


  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.
 
 I think the spec should say that it is an error or undefined
 depending on whether GHC supports reentrant finalizers or not.

Yes, it will work in GHC.  makeForeignPtr is easily implemented in terms
of newForeignPtr, using a foreign import dynamic.

  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.

Heh, I distinctly remember several complaints from *you* in the past
when things have changed in GHC!

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



RE: ffi howto

2002-07-30 Thread Simon Marlow

 If someone could post an example of a hs and a c file and 
 how to compile 
 it with ghc, i would be very apreciative.  I have looked at
 
 http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-ff
 i-ghc.html
 
 for a long time, and I can't figure out how to reproduce the 
 example.  I 
 have noticed that if you name your hs file M.hs as the page 
 says, then ghc 
 will produce M_stub.h instead of the included foo_stub.h 
 that the c main 
 program lists.  I've used windowsXP and ghc[rpm] installed on 
 redhat7.3, and 
 still nothing works.

The stub files are named after the original .hs file, so if you have
Foo.hs you'll get Foo_stub.c.  Most people name their files after the
module name, so for example Foo.hs contains module 'Foo' (in fact this
is necessary if you want to use ghc --make or GHCi).

 my best linux output...
 [Jacob@localhost ffi]$ ls
 main.c  M.hs
 [Jacob@localhost ffi]$ ghc -fglasgow-exts M.hs

I think you want 'ghc -c -fglasgow-exts M.hs' here.  Or maybe 'ghc
-fglasgow-exts main.c M.hs' to do compilation and linking in one go.

 /usr/lib/ghc-5.04/libHSrts.a(Main.o): In function `main':
 Main.o(.text+0x4): undefined reference to `__stginit_Main'
 Main.o(.text+0x1b): undefined reference to `Main_zdmain_closure'
 collect2: ld returned 1 exit status
 [Jacob@localhost ffi]$ ghc -fglasgow-exts main.c M_stub.c
 In file included from main.c:4:
 /usr/lib/ghc-5.04/include/RtsAPI.h:125: syntax error before `const'
 /usr/lib/ghc-5.04/include/RtsAPI.h:126: syntax error before `const'

This is a bug in 5.04; #include Rts.h before RtsAPI.h to work around
it.

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



RE: Generating Function Prototypes

2002-07-07 Thread Simon Marlow

 At 2002-07-05 01:17, Simon Marlow wrote:
 
  If specifying a header file with a function prototype is allowed to
  affect the generated code (i.e., the calling convention), 
 then it is
  clear that the Haskell type does not completely determine 
 the calling
  convention. 
 
 I claim that it is not.
 
 Well it does anyway, as my IO Int64 example shows.

No it doesn't ;-)

Your example works fine when compiled with the native code generator.  I
explained (in my previous message) that GHC needs header files and
prototypes in order to generate correct foreign calls when compiling via
C.  This is, IMO, a GHC-specific issue and doesn't have anything to do
with the FFI specification - although confusion could be avoided if the
spec pointed out that some implementations might need access to header
files/prototypes in order to compile the code.

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



RE: Generating Function Prototypes

2002-07-04 Thread Simon Marlow


  Of course, this ignores the detail that while the C compilers are
  generating correct code, they may also be generating warnings about
  alleged type errors - which can be a bit disconcerting.
 
  It is an error, not just a warning, if the prototypes don't match.
  GCC will complain loudly if there's a missing 'const' - it won't
  generate any code at all.
 
 Well, if you disable the warning by giving gcc a consistent story,
 then the code is correct.  (To give gcc a consistent story, don't
 #include any user or system-supplied headers and make sure gcc doesn't
 silently #include any of its own (as it likes to do).)

I don't think it's possible to completely eliminate system headers from
the transitive closure of stuff we include when compiling a .hc file.
I've just taken a look at this, and it seems that while we can eliminate
a lot of the stuff we include, there are some awkward ones: we need
gmp.h for Integer operations, and that includes stddef.h, and HsFFI.h
needs stdint.h to get the int-type limits (perhaps these could be
autoconf'd).

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



RE: Generating Function Prototypes

2002-07-04 Thread Simon Marlow

 I just reread that section and can't see anything that contradicts the
 idea that the FFI implementation ignores any header files provided.
 For example, the phrase:
 
   implements calls to C functions ... as if a function prototype for
the called functions is in scope
 
 can be interpreted as meaning:
 
 1) Will generate code (by generating machine code directly, by
generating C code which is then compiled, or by some other means)
which assumes the existence of a prototype _even if the user does
not supply one_.
 
[I see this as the most obvious interpretation of the phrase.]
 
 2) Will generate C code which #includes any header files the user has
provided.
 
[I see this as a less likely interpretation but it seems to be the
one you intend?]

Neither, I think.  You're taking an operational interpretation of that
phrase, when it is really just talking about the semantics of the call.

For example: a C function which takes a float as an argument has two
possible calling conventions: the argument may be promoted to double
(used by the C compiler when no prototype is in scope), or it may be
passed as a float (used by the C compiler when there is a prototype).
The FFI spec simply says that it is the latter calling convention that
is used.

Whether a header file is supplied or not should not affect the semantics
of the call (I'm pretty sure you agree with this, but we seem to have
lost track of this central concept somewhere along the way...).
Similarly, whether there is a prototype in scope or not should not
affect the semantics of the call.  The FFI spec doesn't say this
explicitly, but I don't think it needs to.

 My reading of the whole section is that every mention of users
 providing header files and function prototypes refers to compiling the
 C code being called not the Haskell code doing the calling.  The
 examples of using foreign import don't show the use of header files
 though the second example needs a header file to compile correctly
 with GHC.

Only when -fvia-C is on.  This is a compiler-specific issue, the FFI
doesn't need to say anything about it.

 If the intent is that any user-provided header files must be 
 obeyed, then
 I think the spec should explicitly say:
 
   When a header file containing a function prototype is not provided,
   the function calling convention employed is undefined.  It may vary
   between different operating systems, between different 
 Haskell compilers,
   and between different functions.

This is exactly what we *don't* want - the semantics should be specified
by the FFI declaration alone, independent of any header files.  Again,
I'm sure you agree with this - but why do you think that supplying a
header file should make a difference to the semantics?

 I attach my rewording of the section.  Note that I am trying to make
 it quite clear that an ffi declaration is not portable unless you
 provide function prototypes except in the special case that your C
 compiler generates the same code with or without a prototype.

I really don't think the FFI spec needs to say anything about this at
all.  If a particular compiler requires prototypes in order to generate
correct code (such as GHC when going via C) then this is a matter for
that compiler's documentation.  Indeed, the GHC User's Guide does
mention this.

[ Heh.  Now I remember why I didn't like being able to specify header
files in the FFI declaration :-) ]

 ps I still think we're better off removing header files completely and
 having the Haskell type completely determine the calling convention
 employed.  But since I'm not getting any takers on that, I'll 
 settle for
 pinning down the spec as tightly as possible.

Aha!

I must have lost track of the discussion because I can't remember at
which point someone said that the Haskell type does not completely
specify the calling convention.

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



RE: More C interfacing issues

2002-07-03 Thread Simon Marlow



 -Original Message-
 From: Alastair Reid [mailto:[EMAIL PROTECTED]] 
 Sent: 02 July 2002 18:34
 To: Ian Lynagh
 Cc: [EMAIL PROTECTED]
 Subject: Re: More C interfacing issues
 
 
 
  Firstly, some ncurses calls return a *WINDOW and others take one as
  an argument but you never actually look at the contents of one
  yourself. I have defined data Window = Window and am using Ptr
  Window for the types of these. However, this means I get a warning
  about an unused constructor. Is there a better way to do this?
 
 Hugs supports:
 
   data Window
 
 and I believe GHC and NHC do too.  (Malcolm, SimonM: please 
 shout if I overstate.)

Yes, GHC does.

 
  Secondly, does anyone have any suggestions on how to provide an
  interface to this?
 
  void getyx(WINDOW *win, int y, int x);
 
  The getyx macro places the current cursor position of the given
  window in the two integer variables y and x.
 
  The type would probably ideally be Ptr Window - IO (CInt, CInt).
 
 The easy way is to use GreenCard (the other ffi frontends may be of
 use too).
 
 Or, you can do what GreenCard does which is to add 3 wrapper functions
 more or less like this:

What's wrong with just doing this in the plain FFI?

data Window
foreign import ccall getyx 
  getyx :: Ptr Window - Ptr CInt - Ptr CInt - IO ()

niceGetYX :: Ptr Window - IO (CInt, CInt)
niceGetYX win =
 alloca $ \py -
  alloca $ \px - do
   getyx win py px
   y - peek py
   x - peek px
   return (x,y)
   
Have I missed something?

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



RE: Generating Function Prototypes

2002-07-03 Thread Simon Marlow

 Of course, this ignores the detail that while the C compilers are
 generating correct code, they may also be generating warnings about
 alleged type errors - which can be a bit disconcerting.

It is an error, not just a warning, if the prototypes don't match.  GCC
will complain loudly if there's a missing 'const' - it won't generate
any code at all.

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



RE: Minor tweaks to ffi addendum

2002-06-03 Thread Simon Marlow

 section 5.5:
 
   It's going to be really hard to implement ForeignPtr as specified.
   The problem is that invocation of the cleanup function is triggered
   by the garbage collector.  I don't want the garbage collector to be
   recursively invoked so I don't want the garbage collector to
   directly invoke Haskell function.  The Hugs garbage collector is not
   supposed to be a mutator of the heap - so putting a simple wrapper
   round the garbage colector won't work.  And there's no mechanism
   outside the GC to look for cleanup functions to execute.
 
   GHC gets round this by scheduling a (preemptive) thread to execute
   the cleanup code.  How on earth does NHC get round this?  Does
   anyone have a suggestion for how it might be implemented in Hugs?
 
   Proposed change: none at present but I'm deeply sceptical of a
   design which takes a simple task (invoke a C cleanup function) and,
   for no discernable reason, generalizes it to the point that it 
   requires a much more complex runtime system.

I've attached some mail I dug up on the subject, from before the
creation of [EMAIL PROTECTED] (there's more in the archives of that list).
The upshot is:

  - Haskell finalizers are much more in keeping with the general
philosophy of the FFI: do as much in Haskell as possible.  It
looks a bit strange if you have to do your allocation in Haskell
but deallocation in C.

  - If we forced finalizers to be C functions because calling Haskell
from the GC is inconvenient, then you have to add a constraint
that the C function invoked from a finalizer can't call any
functions foreign-exported from Haskell land.  That's an annoying
constraint to have to add, because it means that C libraries
can't be transparent w.r.t. whether they invoke Haskell code or
not (actually the hs_init() problem that someone else brought
up recently also has this side-effect).

Malcolm can comment on exactly how nhc98 handles the finalizers, but I
believe that there's a list of pending finalizers maintained by the RTS
which are run on re-entry to Haskell land.   The equivalent would be to
add a check in Hugs's eval loop, I imagine.

 Table 2 (section 6):
 
   Is there a reason to be so coy about the concrete C types used for
   HsChar, HsFloat, HsDouble and HsBool?
 
   Proposed change:
 
 C symbolHaskell Symbol  Constraint on concrete C type
 HsChar  Charunsigned char

HsChar is an unsigned 32-bit int in GHC.  We probably ought to say that
the type is unsigned, at least - and the Haskell 98 standard requires
that it can at least contain all the Unicode character values (20
bits?).

Cheers,
Simon


---BeginMessage---

* The type of the second argument of makeForeignObj (the finalizer)
  has been changed from Addr to IO (). This is more consistent and
  IMHO Addr is a hack here.

I liked it better before :-( as
makeForeignObj :: Addr - Addr - IO ForeignObj
I would guess that the motivation to make the finalizer argument of
type IO () is that you want to write finalizers in Haskell.
Personally, I like to use the C finalizer, because if I'm importing the
value itself as an opaque type, then why not simply use the finalizer
code opaquely too?  In any case, the C finalizer has type
void finalizer(real_c_type_for_foreign_obj);
Surely if you have this finalizer in the Haskell world, its type
must be something like the following?
finalizer :: Addr - IO ()
rather than
finalizer :: IO ()
So we should really have
makeForeignObj :: Addr - (Addr-IO ()) - IO ForeignObj
writeForeignFinalizer :: ForeignObj - (Addr-IO ()) - IO ()
no?


 To finish the first round, I'd like to make a quick poll: Should
 stable names be mandatory for the new FFI libs or not?

I haven't got any immediate use for stable names, so I would vote to
exclude them (for simplicity) until they are better understood.

* The mapping of StablePtr to a C type.

I go with Manuel's (void*).

* Should addresses on the Haskell side be parameterized by the
  type of the object they point to? How exactly should they be
  mapped to C types?

Yes, I go with (Ptr a).  For simplicity, I think there should be no
compiler-supported mapping to C-types at this stage.
[  In earlier discussions, we thought it would be nice to have
   Ptr Char  --  char*  and so on.  However, you can quickly run
   into tricky cases once the types become more complex, e.g.
   Ptr (a - IO a)  -  void**()(void*)
]

* Are the lifetime rules for ForeignObj (section 2.4 of the FFI
  document) satisfying?

I'm still not sure that I fully understand the difficulties with
ForeignObj finalisation in systems other than nhc98, so I'm reasonably
happy with the current (minimal) rules.

Regards,
Malcolm

---End Message---
---BeginMessage---

To summarize the comments on the 1st shot, I've changed the proposal
in the following ways:

   * `Marshalable' has been renamed to `Storable'. I like 

RE: Type promotion in ccall arguments

2002-03-14 Thread Simon Marlow

  I can't remember whether this has come up before, but to my surprise
  I've just discovered that FFI foreign import declarations don't
  contain enough infomration to be able to determine the correct
  calling convention for a given C function.
 
 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*.

 If we don't like having to remember the C promotion rules ourselves,
 we could write a tool to do it for us.  The ffi is supposed to be a
 _mechanism_ to let you call things and on which you can build more
 convenient layers.  In this case, you can do that so there's no
 problem with the ffi.

I have no problem with this - indeed, I fully agree that we shouldn't
extend the FFI to deal with C's strange promotion rules.  Nevertheless,
we need to say that we're taking this approach.

Similar problems occur with foreign exports: if you declare a foreign
export with Float arguments (eg. see addFloat in section 3.4 of the FFI
doc), does that correspond to a C function defined like this

   float addFloat(a,b) float a,b; { return (a+b); }

or this

   float addFloat(float a, float b) { return (a+b); }

Clearly the latter form is the desired one, but the FFI addendum should
note that, and say that in order to correctly call the function from C
you must have a visible prototype.

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



RE: FFI Addendum, CVS Id 1.19

2001-10-31 Thread Simon Marlow

 A revised version of the FFI Addendum including all issues
 of the last discussion is now available from

Look good...

 New stuff to check
 ~~
 * Section 5.10: Extended handling of IOError (slight variant
   of SimonM's proposal)

This is fine for now.  The slight lopsidedness of the IOError design is
still bothering me though: there's no way to extract the IOErrorType
from an IOError, instead we have these clunky isXXXError things.  It
might be more consistent in the long run to add

ioeGetType :: IOError - IOErrorType

(to go with ioeGetFilePath, ioeGetHandle  ioeGetErrorString), and to
add instance Eq IOErrorType.  The reason I didn't suggest this initially
is because it would be hard to nhc98 to adopt this design, because it
doesn't store IOErrorTypes in IOErrors, unlike GHC.  This is a subject
for the libraries community to discuss, though.

 * Section 6: hs_init()  friends
 
 Open points
 ~~~
 * Interaction of FFI Addendum with Libraries Addendum: I
   propose to *not* mention anything about the new libraries
   hierarchy now.  The Libraries Addendum will have to give a
   mapping of old to new names for all standard modules
   anyway.  I'd rather have the names for the FFI modules
   in the Libraries Addendum.

Ok.  In GHC 5.04 the libraries will still be available under the names
in the FFI spec by using a compatibility package (i.e. you'll still be
able to say -package lang and get pretty much what you get now), but by
default you'll get the hierarchical names.

For the new libraries I think we'll want to move a few things around
anyhow: there are several things in the FFI libraries that don't really
belong there, but have to be there because there is no other standard
specification of their existence.  eg. the IOError stuff,
Foreign.unsafePerformIO, MarshalError.void, and did
MarshalUtils.withMany disappear by the way?

I like the hs_init() family in HsFFI.h.  It might be hard to implement
properly in GHC though, because we have to do module initialization and
there's no easy way to tell what Haskell modules are linked into the
program - hence GHC's extra argument to startupHaskell().  One (not very
attractive) possibility is to require that the program contains a module
Main which indirectly imports all the other modules in the program.

A couple of other minor things:

 - I would delete the last paragraph of section 3, it is just
   repeating what was said in section 2.

 - we should be consistent about finalize vs. finalise.  The API
   uses finalize, so the text should too.

Cheers,
Simon

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



RE: FFI Report, CVS Id 1.11

2001-08-21 Thread Simon Marlow


 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.

This makes me slightly uneasy because the FFI specification will
conflict with the new library specification that is currently evolving.
For example, the names of all the modules are different (eg. CForeign -
Foreign.C).  Now, the FFI spec is clearly much further along than the
library spec, so I don't want to hold it up, but I think it would be
useful if we could agree on what direction we want to go.  

My suggestion is that, since the new library spec will hopefully be
adopted by NHC, Hugs and GHC, that the FFI and library proposals may
co-exist and agree on the specification of the FFI modules.  That means
changing the FFI spec at a later date to accomodate the changes made as
a result of the library reorganisation.

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

ok, but note that there will be some overlap with the library spec.

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

We can move it to Data.List.withMany in the new library hierarchy.

 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.

One module is fine with me.

I have a couple of other points:

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


IOError
~~~

One thing that bugs me about writing FFI code at the moment is that
there isn't a portable way to generate an IOError except through
CError.throwErrno and friends.  There's also no way to change the info
(location, filename, handle) in an existing IOError.  This is the single
cause of non-portability in a lot of the FFI code I've written recently.

Also, we currently can't provide a portable version of CError.hs.

I'd like to see something like this:

-
data IOErrorType -- abstract
mkIOError :: IOErrorType
- String
  - Maybe FilePath
  - Maybe Handle
- IOError

alreadyExistsError :: IOErrorType
alreadyInUseError  :: IOErrorType
...

addIOErrorLoc:: String - IO a - IO a
addIOErrorLocAndPath :: String - FilePath - IO a - IO a
-

This doesn't require any more functionality than is already required by
Haskell 98 (although perhaps the range of IOErrorType could be expanded
somewhat), and it should sit just as well on top of Nhc's implementation
of IOErrors as GHC's.  Furthermore it would let us provide a portable
implementation of CError.hs.

The addIOError functions are very useful.  Quite often an error is
generated by throwErrno in a function which is a long way from the one
which the consumer of a library initially called; for example when I get
an error from Directory.renameFile I want the error message to say
Directory.renameFile and contain the filename that I passed to
renameFile.  So you'd implement renameFile as

renameFile file1 file2 = 
  addIOErrorLocAndPath Directoy.renameFile file1 $ do
   ...

Cheers,
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-13 Thread Simon Marlow

I'm probably about to get my head bitten off for this, but here goes:
would it be possible to move H/Direct in the direction of using the FFI
libs?  For a few reasons:

  - deprecated features are going to be removed at some point.
In fact, I've removed them all in the new Core Libraries.

  - there's lots of duplicated functionality.
 
  - one might be able to mix H/Direct and hand-written FFI code.

I realise this would probably be a lot of work, but then of course
H/Direct will benefit from improvements to the FFI libs, like
stack-allocation (if I ever get around to doing it).

Cheers,
Simon

 -Original Message-
 From: Sigbjorn Finne [mailto:[EMAIL PROTECTED]] 
 Sent: Thursday, July 12, 2001 3:46 PM
 To: Simon Peyton-Jones; [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Subject: Re: Trying to build HDIRECT with ghc-5.00.2
 
 
 No, it was just a bug that was introduced somewhere
 on the road to GHC5. The version of Int in the repo does
 the right thing now.
 
 --sigbjorn
  
 - Original Message - 
 From: Simon Peyton-Jones [EMAIL PROTECTED]
 To: Sigbjorn Finne [EMAIL PROTECTED]; [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Sent: Thursday, July 12, 2001 01:04
 Subject: RE: Trying to build HDIRECT with ghc-5.00.2
 
 
  | (*) - 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
 

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



RE: Again: FFI syntax

2001-05-14 Thread Simon Marlow

* Silly combinations like an unsafe label or 
  a dynamic import with a given C-name don't exist.

But now we have all new silly combinations, like

foreign export dynexp foo :: ...
and
foreign export dynimp foo :: 
and
foreign export foo foo :: ...

the extent field needs to be separated into import-extent and
export-extent, I think.

Can we make the static optional?  It wouldn't introduce any ambiguity,
and it would save characters in the common case.

I like '', but I'm less sure about '!' - this feels like we're getting
a little too cryptic.

Cheers,
Simon

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



RE: FFI Definition

2001-05-07 Thread Simon Marlow

 I still don't understand the dynamic library stuff related to 
 fname. Is
 it a hint for a compiler to link against a given library? Any compiler
 surely has some kind of option/pragma for this already. What should it
 mean when there is a corresponding static lib, but not a dynamic one? 
 Most of the time one doesn't really care about this. What 
 should it mean
 for an interpreter? dlopen-ing? How should the condition
 
... if the external entity has to be obtained from a dynamically
 loaded library ...
 
 be implemented, i.e. when does fname simply denote the header to
 #include and when does it denote something related to a DLL? It looks
 like mixing two unrelated concepts here.

I thought we agreed to remove the specification of libraries from the
FFI, and leave it to some compiler-dependent mechanism.  As Sven points
out, there are going to be times when you really don't want a library at
all, or in any case not one with the same name as the header file, and
there will be cases where you want several libraries in some
system-dependent order that shouldn't be placed in the source code.

GHC already has such a mechanism: the package system, and additionally
using fname as a library spec would make our lives somewhat harder.  I
suggest just deleting the sentence Moreover ... may be made. on page
6.

Cheers,
Simon

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



RE: Revised FFI syntax + typing

2001-05-04 Thread Simon Marlow

  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.

Cheers,
Simon

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



RE: Revised FFI syntax + typing

2001-05-02 Thread Simon Marlow


 -- allowed for import/export
 callconv : 'ccall'   -- default
  | 'wincall'
  | 'stdcall' -- deprecated, same as wincall
  | 'cplusplus'
  | 'jvm'
  | 'dotnet'

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.

 word_ty  : 'Word8'
  | 'Word16'
  | 'Word32'
  | 'Word64'
  | 'Word'-- GHC extension

Why is Word a GHC extension?  Someone remind me?

Cheers,
SImon

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



RE: unsafePerformIO and unsafeInterleaveIO

2001-03-22 Thread Simon Marlow

Alastair Reid writes (on the FFI mailing list):

 ps I wonder if it'd be possible to merge them by doing this 
 in the hslibs repository:
 
 1) Move the STG Hugs ifdefs out of the way:
 
find . -name '*.[l]hs' | xargs perl -p -i 
 -e's/__HUGS__/__STG_HUGS__/'
 
The __HUGS__ label made sense when I expected CLassic Hugs 
 to be replaced by STG-Hugs
- but it wasn't so it should be renamed.
 
 2) Merge in the current Classic Hugs libs (using ifdef __HUGS__).
 
(There's a question of what to do with the Hugs libs which 
 don't exist in
the Hugs-GHC standard.  I imagine that GHC merrily puts 
 GHC-specific files
into the repository and that'd be the thing to do with 
 Hugs files.  In each case,
a giant ifdef round the whole file would prevent it from 
 troubling the other party.)

 3) Add enough infrastructure to make it easy to checkout a 
 working version of Hugs
based on the hslibs repository.

Rather than doing this, if there is effort available at the Hugs end I
would urge them to participate in the discussion of the new library
proposal.  The result will be an evolution of hslibs, so I'm not keen to
put in too much work on hslibs until the design is settled.

The plan for the new libraries is to have a central compiler-independent
repository for the source.  It'd be great if Hugs joined in too.

Cheers,
Simon

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



RE: cpp

2001-02-23 Thread Simon Marlow

  hsc2hs is in ghc-4.11.
 
 Did I miss the last 3 releases?  I'm still stuck with 
 something between 4.08.1
 and 4.08.2 waiting for a debian package and freebsd port to 
 appear for 4.08.2.
 :-)

4.11 is the current devel version, which will be released as 5.00.

I submitted the 4.08.2 port to the FreeBSD folks just after the release,
but they haven't committed it yet.

Cheers,
Simon

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



RE: Summary of current change suggestions

2001-02-23 Thread Simon Marlow


 On Fri, 23 Feb 2001, Fergus Henderson wrote:
 
  OK, now how about things where you need to #define symbols before
  including the header file?
 
 Choose one:
 1. Write a forwarding header which #defines and #includes.
 2. Use compiler-specific switches to get #defines (-D and 
 -optc-D in ghc).
 3. Extend the proposed FFI to have define as well as include.
 
 Unfortunately option 1 doesn't always work well on ghc, because Stg.h
 (included into .hc files) indirectly includes headers like stdlib.h 
 *before* user-specified -#include options, so symbols like _BSD_SOURCE
 are defined too late to have any effects. This should be fixed.

I agree.  Would it be fixed by just #including Stg.h after any
-#includes, or would that create more problems?

Cheers,
Simon

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



RE: Modification to foreign import/export

2001-02-22 Thread Simon Marlow

 If we want to rule cpp as out of bounds (a very worthwhile 
 but difficult goal),
 then we need to think about how to avoid conditional compilation too.

I think the goal is not to avoid the use of cpp, but rather to avoid
mentioning it in the spec.  In practice, many people will be using cpp
(one way or another) when they write a C-library binding.  Conditional
compilation is a fact of life, I don't think it's worth trying to avoid
- but at least there's no need to mention it in the FFI spec.

Cheers,
Simon

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



RE: Summary of current change suggestions

2001-02-22 Thread Simon Marlow


   foreign import ccall "gtk/gtk.h:gtk_window_new" 
 windowNew :: CInt - IO (Ptr Window)
 
 If the . are omitted in the include specification, it
 corresponds to an #include"...".

Don't forget you might need multiple includes, eg. sys/types.h 
sys/socket.h for socket(), and ordering is important.  Multiple
includes could be separated by commas.

I agree that adding the include spec to the foreign import declaration
is a good idea because of the cross-module inlining issue (I'd forgotten
about that).

Marcin: I guess hsc2hs should have some magic to insert the include
specs automatically :)

Cheers,
Simon

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



RE: Summary of current change suggestions

2001-02-21 Thread Simon Marlow

I've kept pretty quiet on this issue before, because I didn't have a
strong view.  Now I'm concerned that some of the suggestions people are
making would take the design in the wrong direction.  

   * specifying libraries in the source isn't the right way to
 go.  Library names change independently of APIs, and can be
 platform-specific.  

 This should be a compiler-specific feature: eg. GHC uses package
 specifications to identify libraries.  Addtionally allowing
 libraries to be specified in the source would just be a pain for
 us.

   * specifying include files in the source is fine; but I'm actually
 quite happy to leave this to an external tool like hsc2hs
 to sort out rather than adding extra syntax to the language,
 but that's just me.  If we really must add new syntax, let's
 make it as general as possible to accomodate future design
 enhancements.  I'd go with

  foreign decl cinclude "foo/bar.h"

 in other words,

foreign decl VARID [ STRING ]

Cheers,
Simon

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



RE: Typing f.e.d.

2001-02-12 Thread Simon Marlow


 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.

Sounds reasonable to me.

Simon


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



RE: Let's get this finished

2001-01-15 Thread Simon Marlow


 On Mon, 15 Jan 2001, Simon Marlow wrote:
 
  data UnsafeCString
  withUnsafeCString :: String - (UnsafeCString - IO a) - IO a
  
  where an UnsafeCString is valid only in an argument position of an
  unsafe foreign import.
 
 Much of the conversion stuff would have to be done in a different way.
 An additional internal interface to conversions implemented in C
 (with ByteArrays instead of Ptrs), pointer arithmetic moved from
 Haskell to C, and in future hard to mix with Handle I/O done on
 Ptrs.

Hmm.  You're right, unfortunately :(  This is depressing.

  I still can't think of a good way to do this in general.  Perhaps
  enhancing the garbage collector so that it could "pin" objects - but
  you've still got the problem of keeping the lifetime of the 
 ByteArray
  in sync with the Ptr.
 
 Lifetime is not a problem:
 withByteArray :: ByteArray - (Ptr a - IO b) - IO b
 
 (And now we know that the ByteArray type should be parametrized!)

Well, the reason I said this was a problem was because I was trying to
avoid the overhead of the exception handler or continuation in
withByteArray.

Actually we can do this right now: you allocate a large ByteArray (= 4k
ish) to make sure it gets allocated in immovable space, and then use
touch# to keep it alive.  You get through a lot of memory this way, but
it should be faster than malloc/free.  I'll do some experiments.

Cheers,
Simon

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



  1   2   >