Re: Haskell and Maple FFI

2004-09-20 Thread Alastair Reid

 Examples ( taken from Open Maple )

 ALGEB M_DECL MyStats( MKernelVector kv, ALGEB *args )
 {
 ALGEB mean, sd, f;

 if( 1 != MapleNumArgs(kv,(ALGEB)args) ) {
 MapleRaiseError(kv,one argument expected);
 return( NULL );
 }
 ...
 /* return the pair */
 return( ToMapleExpressionSequence(kv,2,mean,sd) );
 }

 Is it what do you mean ?

Yes, now use Haskell's ffi to import all those OpenMaple calls you made in the 
above.  That is, MapleNumArgs, ToMapleExpressionSequence, etc.

Having done that, translate the code into Haskell in the obvious way and check 
it works.

Try a range of examples, figure out what works and what doesn't work, figure 
out where the order of things matters and where it doesn't.

After you've done a bunch of examples, show us them and we can suggest how to 
use type classes to reduce most maple calls to just a line or two of Haskell 
code.

 I don't know on Marshalling/UnMarshalling...

Marshaling/unmarshalling is converting the argument list from Haskell (or, for 
that matter C) representation into Maple representation.  Half the code in 
your example was doing this.

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


Re: Haskell and Maple FFI

2004-09-17 Thread Alastair Reid

 I would like to implement a new calling convention for Maple
 language, so that programers in Haskell may call for Maple routines.
 Both languages are intereseting for cooperation, due to its symbolic
 expresiveness.

Making it possible to call Maple would be very cool.  Can you give more detail 
about Open Maple?

If I was doing this, I'd start by writing some C code that interfaces to 
Maple.  After that works, I'd translate it into Haskell.  That is, I would 
use the FFI to invoke the Maple FFI functions for pushing arguments, popping 
results, etc. and use the the FFI libraries which have lots of useful 
functions for marshaling arguments from Haskell to other formats.

Start with something simple (e.g., a single argument function like 'sin'), 
prototype in C, translate to Haskell.  At this point, don't worry too much 
about the fact that the simplest function call seems to require 10-20 lines 
of code - we can suggest ways to fix that.  Keep trying new features (2 
arguments, strings, calling both Haskell-Maple and Maple-Haskell, etc.) 
[The Open Maple manual probably has a list of examples used to illustrate the 
interface - start by doing all those.]  If it isn't obvious how to do it or 
it just won't work, step back and write a prototype in C.

Ask us as you run into problems.


Once you can do all that, there's a bunch of tricks you can play with 
typeclasses to reduce the number of lines of code you have to write from 
10-20 lines down to just one or two.  (Ross Paterson has a very nice scheme 
for doing this - but I can't find it in the mail archives at the moment.)

--
Alastair Reid

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


Re: C.Types

2004-09-06 Thread Alastair Reid
On Monday 06 September 2004 14:10, Daniel Müller wrote:
 I try to use a Function calc, which is written in C (CalcType = Int):
 [...]
 Unfortunately I got an error. What shall I do?

Telling us what the error is (cut and paste from the terminal is best) would 
be a start.  If the program compiles but gives an unexpected answer, say what 
answer you get and what you expect.  What compiler and version are you using?

Providing a _complete_ example we can try ourselves would be another thing to 
try.

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


Re: PIC status

2004-08-01 Thread Alastair Reid
[Redirected to [EMAIL PROTECTED] from [EMAIL PROTECTED]

Wolfgang Thaller wrote:
 [lots of stuff about dynamic linking/ghc/PIC deleted]
 So what's left to do is the following:
 [...]
 7) Devise a way of telling GHC that a foreign import is imported from a
 DLL (for Windows); something like __declspec(dllimport) in Windows C
 compilers. We should have thought of this before the FFI spec was
 finalized...
 [...]

Can you explain point 7?

How is a foreign import from DLL different from a foreign import from 
statically linked files or from foreign import of a function pointer?
Do you have to do something different to cause the DLL to be loaded or do you 
have to invoke the function using a different calling convention or both?

--
Alastair Reid
___
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 Alastair Reid

 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.

Maybe the code generated by Hugs should be something like:

#ifdef MACROS_ARE_COOL
#undef malloc
#endif

?

(I'm not likely to implement this anytime soon but if someone has the energy 
to do so, go right ahead.)

From what I know of NHC, it probably has the same extension and would benefit 
from the same cleanup.

--
Alastair
___
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-08 Thread Alastair Reid

Ian Lynagh writes:
 Some C libraries (curses is the one I have to hand) provide macros in
 addition to functions in some cases for efficiency reasons. If you use
 the FFI to import such a function thus:

I was a bit confused by what Ian meant by this so, in case it helps others, 
here's an extract from curses.h.

extern NCURSES_EXPORT(int) wstandend (WINDOW *);/* generated */
#define wstandend(win) (wattrset(win,A_NORMAL))

There seem to be a substantial number of these:

  $ grep generated /usr/include/curses.h | wc -l
  117

As far as I can see, there is no conditional compilation to let you turn the 
macros off so you would have to write 117 individual #undefs, 117 stub 
functions or whatever.

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.  For that reason I vote for:

 Surrounding the function with parentheses so the macro doesn't match.
 The offending line above would be
 _ccall_result = ((wstandend)((_ccall_arg1)));

where the decision to insert parens is decided by a command-line flag.  
(Ideally, this flag would affect foreign imports in that file but not any 
obtained from imported modules.)

I like this approach because it means that we don't have to strip the parens 
off when using the other compilation techniques such as GHC's NCG or Hugs 
generating stub functions for everything.

Alternatively add an appropriate set of #undefs for this particular file.  The 
following comes close to doing the job.

grep generated /usr/include/curses.h
  | perl -pe 's/^.*\)\s+(\w+).*/#undef \1/'

Stick the result in a header file like this:

  curses_wrapper.h:

#include curses.h
#ifdef __GHC__
#undef macro1
...
#undef macro117
#endif

and use curses_wrapper.h instead of curses.h in the Haskell code.

--
Alastair Reid

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


Re: Request: withArrayLength

2004-03-24 Thread Alastair Reid
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.]

   I'm a bit uncertain over how many modules should live in
   this new hierarchy.  The easy answer is just one - by the time
   we have more than a module's worth of code, it's time to
   add some of them to the standard.  An alternative is to mirror
   the structure of the standard libs:

 Foreign.NonStd.{C,ForeignPtr,Marshal,..}
   
   which would be useful if we don't want to bump the ffi version
   number too often.

2) I think the evolution of the ffi std from Sigbjorn's original
   foreign import/export proposal benefited hugely from things like
   the QForeign library where ideas could accumulate and become
   consistent, portable, etc.

3) We don't have any way to do version numbered packages at 
   present but we need somewhere to put the code now.

--
Alastair

[Detail: The GHC folk might want to move Foreign.Concurrent to 
Foreign.NonStd.Concurrent.]
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: newtype abstraction problem

2004-02-04 Thread Alastair Reid

 I can't see a simple solution.  Perhaps we just declare that when a
 newtype is exported abstractly, it's suitability as a foreign argument
 type is still visible.

This feels a little like the global visibility of class instances.
If I export a type T abstractly, all its instances are exported too.
(In that sense, SimonPJ's old CCallable/CReturnable classes were right on the 
money.)

--
Alastair

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


Re: How does one use pass by reference functions using the ffi?

2004-01-25 Thread Alastair Reid

   Say I have a function somewhere in c land with the following declaration:

 void doStuff( int a, int b);

   What would the appropriate Haskell wrapper for this function look like?
 I'm looking to construct a haskell function of the type:

The following (untested) Greencard code ought to do the trick.

%fun doStuff :: Int - Int - IO (Int,Int)
%code doStuff(arg1,arg2)
%return ({*arg1},{*arg2})

--
Alastair Reid

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


Re: Handle to haskell data

2003-12-01 Thread Alastair Reid
On Sunday 30 November 2003 6:43 pm, David Waern wrote:
 Hi. I want to know if it is possible via FFI and GHC to allocate
 haskell data structures and return some kind of handle to their internal
 representation in the haskell runtime to another language that calls
 haskell code (c/c++).

Use StablePtrs.

These are more or less a direct pointer to the Haskell data structure
with just enough magic to keep the garbage collector happy.

You can read more about StablePtrs in this paper:

  http://www.reid-consulting-uk.ltd.uk/alastair/publications/gfpw94/index.html

Since that paper was written (1994), the names of the operations and their 
types has changed quite a bit.  See the current specification for details:

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

--
Alastair Reidwww.haskell-consulting.com

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


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

2003-11-01 Thread Alastair Reid

 I wonder how this discrepancy between the libraries and the
 report arose. 

For what it's worth, the library has been that way since June 28, 2001:

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/base/Foreign/
Storable.hs?rev=1.1content-type=text/x-cvsweb-markup

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/base/GHC/
Storable.lhs?rev=1.1content-type=text/x-cvsweb-markup

This seems to be copied from Marcin's QForeign which had the same type from 
Jan 2, 2001 - March 18, 2001 (i.e., the entire lifetime of the library)

http://cvs.sourceforge.net/viewcvs.py/qforeign/qforeign/lib/
QStorable.hsc?rev=1.7view=markup

 Did I simply make a mistake when writting the
 report (then, this would qualify as an error in the report
 anyway)?

On this evidence, it looks like it's an error in the report.

The type is certainly consistent with the type of plusPtr if you
think about implementing peekByteOff like this:

  peekByteOff p o = peek (plusPtr p o)

And, since peekByteOff is primarily for use when peekElemOff doesn't work 
(i.e., for structs), it makes sense to change the type.

--
Alastair Reid

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


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

2003-10-31 Thread Alastair Reid
I think it's ok for the finalizer function to delete the environment object if 
it wants isn't it?  

This isn't always the right thing to do but I think it is in the common case 
that there is a unique environment object for every finalized object.

In the other common case that there is a single environment object for a set 
of objects (e.g., for all objects of the same 'type'), the finalizer might 
decrement a reference count on the environment object.

Have I missed some subtlety?

--
Alastair Reid


 Regarding

   type FinalizerEnvPtr env a = FunPtr (Ptr env - Ptr a - IO ())

   newForeignPtrEnv :: FinalizerEnvPtr env a -
   Ptr env - Ptr a - IO (ForeignPtr a)
   addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -
   Ptr env - ForeignPtr a - IO ()

 Doesn't this mean that the env must be either static storage (gaining
 nothing) or dynamic storage that cannot be reclaimed (which brings us
 back to where we started)?

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


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

2003-10-31 Thread Alastair Reid
[As I was about to send this, it occured to me that maybe you had made a typo 
and meant to write 'peekByteOff' instead of 'peekElemOff'?  This seems less 
dodgy since peekByteOff is more usually used to access elements of structs 
where different elements have different types.]


I think the report is right and the libraries should be fixed even if a lot of 
code has to be changed to make the two agree.

With the report version:

1) Simple programming errors are readily caught.

2) Less type information needs to be written
   (obviously at the cost of not catching the
   type errors in (1).)
   That is, if you specify the type of the value
   being peeked, you can infer the type of the pointer
   and vice-versa.

3) If you want to do something funny, you have to 
   explicitly cast the pointer to make it happen
   which alerts readers to the fact that you're 
   doing something funny.

To be honest, I can't think of many cases where I would want the 
types you propose.  peekElemOff is basically for arrays where all elements 
have the same type - why would you want to treat them as having different 
types?

--
Alastair Reid

 Never say never... The signatures for peekElemOff and pokeElemOff in the
 report are less general than the ones in fptools/libraries/base:

 peekElemOff :: Storable a = Ptr a - Int - IO a

 vs.

 peekElemOff :: Storable a = Ptr b - Int - IO a

 (same for pokeElemOff). The latter is more flexible and is more in line
 with the signatures of plusPtr/minusPtr. Furthermore, changing such a basic
 function would probably break quite a lot of code, so I propose to change
 the report, not the libraries.

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


Re: The Errno Story

2003-07-27 Thread Alastair Reid

 John's first suggested alternative above seems very appealing to me, as it
 seems neatly to fix the fundamental design flaw in `errno`: that
 determining the success/failure of a system call is separated from the call
 itself. 

Slightly off-topic but it reminds me of one of my pet peeves with C...

I think the design flaw is in C and that is merely reflected in the C library.  
If you listen to the propaganda, C is just a portable assembly language and, 
in many ways, C is just that.  One of the big differences though is that in 
assembly language, there is no problem returning multiple values -just load 
up multiple registers or put multiple values on the stack- but in C, there is 
no good way to return multiple values.

--
Alastair Reid

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


Re: stdcall

2003-07-23 Thread Alastair Reid
On Tuesday 22 July 2003 3:20 pm, Ross Paterson wrote:

 OK, so the thing I want shouldn't be called stdcall, but it would be useful
 (and is already being used).

Yes to both.
Especially so if any other platform has two commonly used calling convention.

--
Alastair

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


Re: stdcall

2003-07-19 Thread Alastair Reid
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.

2) But, most functions in Win32.h and friends are declared something like:

   pascal rty foo(argtys);

3) On Win32, the pascal qualifier is included not just on Win32-specific 
functions but also to functions available on other platforms (but without the 
pascal qualifier): ansi functions, opengl functions, etc.

If that is so, I think we want to have two separate kinds of calling 
convention.  I'll number the calling conventions to avoid getting into 
discussion about what to call them too early.

calling convention 1:  call using the C calling convention.  That is, use this 
calling convention if a function is declared:

   rty foo(argtys)

This is useful when the user (or his ffi preprocessor) wrote foo themselves.


calling convention 2: call using the dominant calling convention on that 
platform: pascal on windows, C on unix.


Possible names for these are:

convention 1: ccall or C
convention 2: stdcall 

I would make convention 1 be the default if none is specified or have no 
default.

A



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


Re: More Finaliser Trouble

2003-07-13 Thread Alastair Reid
 [...] doesn't answer the question of why these things have changed [...]

We dropped Haskell finalizers because neither Hugs nor NHC could implement 
them and implementing them would pretty much require them to implement 
preemptive concurrency (i.e., multiple threads each with their own stacks).

These issues were considered important because one goal of the ffi spec was to 
improve portability between implementations and also because we explicitly 
decided not to do anything that requires concurrency or other H98 extensions.

--
Alastair Reid

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


Re: again: nullForeignPtr

2003-07-08 Thread Alastair Reid
 The need for nullForeignPtr arises when a function expects
 a pointer to some data structure or a null pointer. In this case I cannot
 make the foreign import have the type (Maybe (ForeignPtr ()) since it's not
 accepted by the FFI.

I guess I've mostly used this trick with GreenCard whcih supports this idiom 
quite well.

Mind you, ForeignPtr isn't accepted by the FFI either so the code you 
currently use to marshall them could be modified to marshall Maybe 
(ForeignPtr ()) instead.

--
Alastair

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


Re: again: nullForeignPtr

2003-07-07 Thread Alastair Reid

 the discussion on ForeignPtrs without finalizers didn't come to a
 conclusion. I specifically need the nullForeignPtr which was easy enough
 with the FFI of GHC 5.04:
 [...]
 do I have to create a dummy C function?

Yes, create a dummy C function.
(Actually, you could use 'free' since it does nothing if passed NULL.)

--
Alastair

ps Personally, I would use

  Maybe (ForeignPtr a)

in the places where you are currently using a ForeignPtr which could be null 
with 'Just x' being used only when x is not null.

I haven't tried exactly this but I have lots of experience using  Maybe (Ptr 
a) in this way and it works great: Haskell's type system catches errors that 
would be runtime errors in C.




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


Re: new ForeignPtr without finalizers

2003-06-12 Thread Alastair Reid
Manuel:
 In other words, it seem much more likely that one would
 partially apply `newForeignPtr' to a finaliser than to a
 pointer that is to be finalised.  But this is a minor point.

Having written some more ffi code over the last couple of days, I agree that 
this is much more natural so, even though it will break all the packages I 
released in the last week, I now vote for swapping the argument order.

Since this breaks code anyway, we could adopt Dean's proposal to allow lists 
of arguments to newFP and addFPFinalizers without making things worse.  I 
don't think we should do this though since I believe they would always be 
used with singleton or empty arguments and because the list-based versions 
can be trivially added with a foldM if they prove useful.

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


Re: new ForeignPtr without finalizers

2003-06-12 Thread Alastair Reid

 Actually, I think I prefer Ashley's idea of separating the creation of a
 ForeignPtr from the addition of a FinalizerPtr.  So how about:

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

You're proposing a different name for newForeignPtr_?

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


Re: new ForeignPtr without finalizers

2003-06-09 Thread Alastair Reid
On Monday 09 June 2003 4:59 am, Ashley Yakeley wrote:
 OK, I just upgraded to GHC 6.0. How do I create a new ForeignPtr that
 doesn't have any finalizers?

   newSimpleForeignPtr :: Ptr a - IO (ForeignPtr a)
   newSimpleForeignPtr ptr = ??

There is no direct way in the ffi.  You could define a dummy function in C:

  void dummy(HsPtr x) {}

and use:

   newSimpleForeignPtr :: Ptr a - IO (ForeignPtr a)
   newSimpleForeignPtr ptr = newForeignPtr ptr dummy
   foreign import ccall  dummy :: FinalizerPtr
  

It looks like you're using an idiom we didn't think of when designing the 
library.  Can you explain what you're trying to do and whether you think we 
shoud provide direct support for newSimpleForeignPtr (which I'd be tempted to 
call newForeignPtr_).

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


Re: new ForeignPtr without finalizers

2003-06-09 Thread Alastair Reid
Ashley:
 How do I create a new ForeignPtr that doesn't have any finalizers?

Malcolm:
 Why would you want to?

addForeignPtrFinalizer lets you add them later.
I'm guessing that Ashley is making heavy use of this ability.

[What we have at the moment is the ability to attach a non-empty list of 
finalizers to an object.  I don't immediately see a use for an empty list but
my experience with various datatypes is that it is usually cleaner to allow 
the empty or zero case and I#'m hoping that Ashley will demonstrate how it is 
useful...]

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


Re: new ForeignPtr without finalizers

2003-06-09 Thread Alastair Reid
On Monday 09 June 2003 3:48 pm, Manuel M T Chakravarty wrote:
 Andre proposed to allow `nullFunPtr' as a finalizer argument
 to `newForeignPtr' to indicate the lack of a finalizer.
 This seems quite C-ish, but has the advantage that it is
 easy to parametrise functions that internally use
 `newForeignPtr' as to whether there should be a finalizer
 attached.

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

I'm not convinced that merging them into a single function is desirable, but, 
if we wanted to, I think a better FPish solution is to use 

  Maybe (FinalizerPtr a)

Adopting the C idiom seems inappropriate (should use a Haskell idiom for 
Haskell code) and sets a bad example.

Using higher order functions has the problem that the type becomes so general 
that you don't know what you're meant to pass in and certainly can't guess 
that there are only two choices and, despite the hype, function arguments are 
2nd class citizens in Haskell (since you can't print them, compare them, 
etc.)

 I'd propose to

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

I agree with adding newForeignPtr_.  (Presumably the report would define 
newForeignPtr in terms of newForeignPtr_ and addForeignPtrFinalizer.)

I'd prefer to avoid swapping the argument order because of code breakage.

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


Re: How to access defines and enums in a convenient way?

2003-06-06 Thread Alastair Reid

 You want to use a tool to make all this easier.  There are various tools
 available: green-card, c2hs, and hsc2hs are the most commonly-used ones
 these days.

 Alastair Reid wrote a good comparison of the various tools
 (can't remember the link off hand though).

It is in:

  http://www.reid-consulting-uk.ltd.uk/docs/ffi.html

I've been trying to update it recently so there's some new answers to FAQs but 
there's also some empty sections where I plan to write something but haven't 
yet.

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


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

2003-06-05 Thread Alastair Reid
ok, I'm convinced.  The semantics of empty datatypes can be a type inhabited 
only by bottom.

Hugs implements exactly that.

[Except in the special case of a few magical names (Int, Float, etc) when they 
occur in the Prelude (and only then).  Since it is only usable in the 
Prelude, they can be treated as an internal detail and ignored.]

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


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

2003-06-02 Thread Alastair Reid
On Saturday 31 May 2003 10:11 pm, John Meacham wrote:
 This was discussed here before and there seemed to be some support for
 it, but how about adding the empty data declaration extension to the FFI
 spec?

I strongly agree that we should definitely add the ability to declare types 
whose definition is provided externally.  (i.e., provide the feature that 
empty datatype decls currently provide.)

Before adding them, we need to agree on the semantics and syntax (in that 
order I think).

The obvious semantics based on the syntax is:

[[
  The declaration

data T

  introduces a type T whose only value is bottom.
]]

This semantics is obviously flawed though because it would suggest that any 
two values of type T are equal (and equal to bottom) and that optimizations 
based on that equality are valid.  Using an unpointed type (i.e., the value 
is not bottom) or saying there are no values bottom or otherwise don't help.

The correct semantics has to be something roughly like:

[[
  The declaration

data T

  declares a type T whose set of values are defined externally to the
  language. [optional sentence: There are no legal Haskell operations 
  on values of type T.]
]]

If we go with a semantics like that, different syntax suggests itself like:

  external data T

or, better, 

  foreign import data T

I'm not especially keen to change the syntax (especially since the existing 
syntax is so trivial to implement) but if we're going to add this to the
language, we should make sure the syntax and semantics are tolerably
clear and in agreement with each other.

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


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

2003-06-02 Thread Alastair Reid
On Monday 02 June 2003 11:14 am, Malcolm Wallace wrote:
 How about something like:

   The declaration
   data T
   declares an abstract datatype T, whose values and operations are
   defined external to the Haskell language.  Values of T follow
   the semantics of the foreign language, in particular, with respect
   to mutability and the admission of the undefined value.

I don't think we have much choice about whether undefined values are part of 
the type.  If you can create a value of that type:

  x - derefPtr (px :: Ptr T)

then you can create a thunk of that type:

  let y = if expression then x else y

and that thunk can be bottom.

 This raises the question of whether it should be possible to declare
 foreign functions directly over such types, [...]  However,
 I know that nhc98 internally at least uses the former style in order
 to implement built-in types like arrays, big integers, etc.

Hugs implements its builtin types this way too (and did so long before the ffi 
came along).  It works because Hugs magically knows how toi implement Int, 
Float, etc. - it knows about any typechecking rules and, most importantly, it 
knows how to represent and marshall values of builtin types.  If all the 
compiler is given is:

  data T

where T is not a builtin type, the compiler can't possible know how to 
represent or marshall it.  (And since we can already do that using 'newtype T 
= MkT Int8' I don't think we need to add another mechanism.)

Although it is similar, I think

  data Int

with a builtin type is a different thing from what we're doing when we write:

  data T

for some foreign type.

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


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

2003-06-02 Thread Alastair Reid

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

Sorry, I meant peek.

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

Sorry, I was just trying to show how to create a value of type
T which might be bottom.  It would have been easier to use:

  t :: T
  t = undefined

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


Re: Finalizers, again!

2003-03-06 Thread Alastair Reid

 I have just read Hans Boehm's POPL paper on finalizers.  His
 suggestion for the use of finalizers in single-threaded systems is
 to provide a `runFinalizers' routine, instead of relying on the
 asynchronous execution that, as established, requires support for
 concurrency. 

I think there Haskell's laziness and, to a lesser extent, focus on
side-effect free evaluation, makes a significant difference to the
design landscape so what is appropriate in the languages Hans Boehm has
experience of is less suitable for Haskell.

In particular, strict imperative languages lend themselves to
operational reasoning whereas Haskell's evaluation order can baffle
even the experts and writing code with _portable_ operational
behaviour is, I think, impossible with current techniques and tools.
This is exacerbated by the Haskell report which deliberately avoids
the subject and the range of different optimizations implemented by
different compilers.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/


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


Re: Bound Threads

2003-03-06 Thread Alastair Reid

 Does anyone plan to add support for multiple OS threads to Hugs or NHC?

I think it will depend a bit on the complexity so let me sketch how I
think it can be implemented.

First let me outline my current understanding of what 'bound' means.
Consider the following scenario:

  Haskell program is running in OS thread 't1'
  Haskell program calls C function 'foo'.
  'foo' forks a new OS thread 't2'.
  In parallel: 't1' calls Haskell function 'f1' and
   't2' calls Haskell function 'f2'
  'f1' calls C function 'g1'
  'f2' calls C function 'g2'

My understanding is that 'bound' requires that 'g1' be executed by
thread 't1' and that 'g2' be executed by thread 't2'.  It would be
nice if 'f1' and 'f2' could run simultaneously but the ffi is not
going to impose that on us.  If 'f1' were to block on an MVar, 'f2'
could start running and vice-versa.  While 'g1' is running, 'f2' can
run and while 'g2' is running, 'f1' can run.

Based on this understanding, I believe that single-threaded runtimes
could easily implement 'bound' by doing nothing more than using a lock
to ensure that at most one OS thread executes Haskell code at once.
Thus, a global lock would have to be acquired when a bound function is
called or when a thread starts running and the lock would be released
when a thread stops running (completes, calls out to C or blocks).

This sounds pretty simple (a few tricky corner cases to get right but
no major upheaval in the runtime systems) and the locking requirements
are quite modest (so, hopefully, portable) so I think an
implementation is pretty likely to happen.  Timescale will depend on
when people find time or money to do it.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

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


Re: lesson about ffi

2002-12-12 Thread Alastair Reid

Po Popo [EMAIL PROTECTED] writes:

 Hello, I study computer engeneering at University of
 Pernambuco-BRAZIL .I have to present a lesson about FFI and i need
 some help, like explains where i can get the right information and
 tutorials. Its very important to me. Since now im thankful.

I started work on an ffi tutorial.  At the moment it concentrates on
how to use the various compilers, frontend tools to use with the ffi,
etc. but it has pointers to the documentation, mail on the ffi list
about how to use the ffi, etc.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/



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



Re: addForeignPtrFinalizer

2002-11-26 Thread Alastair Reid

Did we ever sort out the original subject of this thread which was:

  Should finalizers on a given foreign pointer be executed in the
  order they were added?

It is obvious what addForeignPtrFinalizer can be used for if this
guarantee is made.  As far as I can recall, no-one has suggested what
addForeignPtrFinalizer is good for if this guarantee is _not_ made.

Hugs makes this guarantee.

I believe NHC can easily make this guarantee if they don't do so
already.

GHC does not make this guarantee but they know how to implement it.

The current ffi spec (release candidate 7) does not make this guarantee.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: ForeignDependencies: The Semantics

2002-11-26 Thread Alastair Reid

Was any decision reached about foreign dependencies?

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



Re: addForeignPtrFinalizer

2002-11-26 Thread Alastair Reid

 I think that should be the reverse order.  For example, if you add a
 finalizer to the result of mallocForeignPtr, you want it to run
 before the thing is freed.  (That's what Hugs does now.)

Sorry, yes, of course.

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



Re: ForeignPtr

2002-11-07 Thread Alastair Reid

 Sorry to ask this again, but I didn't understand the answer last
 time, and the need to explicitly free StablePtr's, Haskell FunPtr's
 and close foreign handles, etc, is surely a serious wart in the FFI
 spec.

I don't understand part of this.  StablePtrs exist so that you can
hand them to C.  [Even if you were to use conservative GC with C] C
needs to tell Haskell when it is finished with the StablePtr.  It does
this an explicit free function.  Haskell's GC cannot safely free
StablePtrs because the assumption is that C has a pointer to it and
has not yet explicitly freed it.

In short, the defining feature of StablePtrs is the need to use an
explicit free function to delete them.  Remove this feature and they
really don't buy you much.

Is there another use for StablePtrs where this is not an issue?

The same seems to apply to FunPtrs and I'm not sure what you mean by
foreign handles


 In Sept 2001 Ashley Yakeley asked why ForeignPtr couldn't be
 generalized, i.e. an interface like (slightly modified from the
 original):

On first glance, this looks cool.  What instances do you envision
(assuming I persuaded you that StablePtr and FunPtr should not be)?

 type Finalizer a = FunPtr (a - IO ())

Let's add that to the FFI spec - useful whether we adopt proxies or not.


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



Re: ForeignPtr

2002-11-07 Thread Alastair Reid

 On first glance, this looks cool.  What instances do you envision
 (assuming I persuaded you that StablePtr and FunPtr should not be)?

 How about Int (for file descriptors, etc)?

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

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.

Trivial to implement, might require an additional layer of boxing in
GHC (maybe in Hugs too - I forget the implementation).

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



Re: ForeignPtr

2002-11-07 Thread Alastair Reid

 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?

But then people will start asking why finalizers have to be C functions... 
(0.5 :-))

I'd say that Finalized would be a fine name for a GHC-specific variant
that allows Haskell finalizers.  Nice clean design, no particular ffi
dependency.  Might cover a useful common case that WeakPtrs perhaps
don't (???).

--
Alastair


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



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

2002-11-07 Thread Alastair Reid

 perhaps ForeignPtr should not be an instance of Eq so people can
 provide their own?

Note that if we did this, we'd want to consider adding an operation

  eqForeignPtr :: FP a - FP a - Bool 

  FP b-- possible variant but not very useful

which lets people test equality of the container and not the contents.

In fact the more I think on it, the more convinced I am that the Eq
instance should compare contaner equality and not contents equality.
The reason is that I believe Eq instances should follow the following
design rule:

 Eq instances should compute observational equivalence

I believe this is satisfied by all Haskell98 types, all the usual
extensions (IORefs and friends) and by derived instances of datatypes.


Just to be clear what I mean by observational equivalence, consider
comparing two IORefs x and y using this code:

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

  One might be able to distinguish two data structures of type [Int]
  (say), by observing how much memory they consume.

This is perfectly true but Haskell semantics doesn't let you observe
this so we'll rule any such 'observations' as irrelevant or invalid.

--
Alastair

ps Careful reading will reveal that I still haven't proposed a
concrete use for eqForeignPtr.  So far, I'm relying on a combination
of gut instinct and the fact that we (i.e., me plus one or more of my
coauthors at the time (Simon PJ, John Peterson, and Simon Marlow)) did
consciously decide to use one semantics instead of the other when we
designed MallocPtrs/ForeignObjs/ForeignPtrs originally.  I thought
about it a good deal harder when I added them than I claim to have
thought about them in the last couple of days.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: White space in ccall impents

2002-11-05 Thread Alastair Reid

Ian Lynagh [EMAIL PROTECTED] writes:
 Is it just me or does the FFI spec not explain what whitespace is
 needed between the components of the ccall impent? 4.1.1 is the
 obvious place for it to be. In particular, even after reading
 between the lines, questions like are multiple spaces between
 static and fname allowed, is a space between  and cid allowed (or
 required) and are tabs allowed seem to remain unanswered.

I remember wondering this when I implemented it in Hugs.  My
understanding of the spec is that the impents contain a sequence of
tokens separated by whitespace.  IIRC, I came to this belief not by
finding something which spells it out but by deciding that any other
interpretation made it impossible to parse the examples in the report
using the grammar in the report.  

If it isn't spelled out explicitly already, it would be good to do that.

In the meantime, I believe the story is that multiple spaces are
allowed, tabs are allowed and any two tokens may be separated by
spaces.  If you catch Hugs behaving otherwise, I'll fix it.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/


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



Re: White space in ccall impents

2002-11-05 Thread Alastair Reid

 token - special |  | fname | cid | whitespace
 special - static | dynamic | wrapper
 fname - ... .h  (... as I don't have [3] handy)
 cid - ... excluding special   (... as I don't have [3] handy)
 whitespace - { ' ' | '\t' }

For what it's worth, Hugs uses 'any non-empty sequence of non-space
characters' where you use '...' and uses different but probably
equivalent contortions where you use specials.

The practical difference from this is that Hugs would probably let you
foreign import things called 'foo[42]' if you wanted.  I guess this is not
what the ffi report intends :-)

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



Re: location of HsFFI.h?

2002-10-30 Thread Alastair Reid

John:
 I was wondering whether there was any standard way to find HsFFI.h?

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

And if using Hugs (forthcoming release), use ffihugs to compile your C code:

Foo.so: Foo.hs foo.c bar.o
ffihugs +G Foo.hs -Lfoo.c -Lbar.o -L-lm

You'll also find the file in ${installdir}/lib/hugs/include/HsFFI.h

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Finalizers: conclusion?

2002-10-22 Thread Alastair Reid

[EMAIL PROTECTED] pisze:
 keepAlive x y ensures that the finalizer for y is not run 
 until after the finalizer for x has run to completion.

Marcin:
 What if I do keepAlive p1 p2  keepAlive p2 p1?  They will never be
 collected?

Correct.

I'm a bit vague about what liveness dependencies are for.

What I was thinking was that you'd use it if the C object for p1
refers to the C object pointed to by p2 and the finalizer for p1
required that the C object pointed to by p1 to be alive.  In this
case, it would be an error to finalize p2 before you finalize p1 and
my semantics is the only one that will work.

If that is what liveness dependencies are for, then the programmer
made a mistake when they wrote:

  keepAlive p1 p2  keepAlive p2 p1

This would mean that the objects pointed to by p1 and p2 both have
pointers to the other and that it isn't possible to finalize them
independently (and, obviously, we have no way to finalize them
collectively, either).


Can those who use liveness dependencies correct my understanding of
what they are for?

--
Alastair






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



Re: Finalizers: conclusion?

2002-10-22 Thread Alastair Reid

John Meacham [EMAIL PROTECTED] writes:
 here are my canidate suggestions:

 * add a subset of Weak pointers 

Can you spell this out in detail.  What are the functions?  What are
their semantics?

 - or -

 * add addForeignDependency :: ForeignPtr a - ForeignPtr b - IO ()

Again, could you spell out the semantics.

 note that breaking these dependencies might be tricky/impossible

This is something I don't understand.  

Why do you have to break dependencies?  Is it to break dependency
cycles?

Also, when do you break dependencies?  e.g., Do C finalizers need a
way to tell Haskell to break a dependency?  Do you manually detect
that some objects have not been collected and speculatively start
breaking dependencies?  If the problem is cycles, would it be helpful
if addForeignDependency detected when it created a cycle and raise an
exception/ set a flag/ etc.


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



Re: The Death of Finalizers

2002-10-22 Thread Alastair Reid

 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!

There's two reasons you might use the function: convenience and atomicity.

I can easily imagine someone modifying a program, thinking that it was
used for convenience, replacing it with non-atomic 'equivalent' code
and breaking the code in a way that will take a lot of testing to
find.  Being explicit that it has this special, important property
protects against that.

But what if I am only using it for convenience and I want to document
that fact?  One could make a good case for adding plain modifyIORef
which may or may not be atomic.  


Or, we can avoid the issue altogether by not adding an atomicity
guarantee.  If you use concurrency, use MVars, if you don't use
concurrency, you don't need it.  

--
Alastair

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



Re: The Death of Finalizers

2002-10-21 Thread Alastair Reid

 [snip] How sad.  It's an unfortunate hole in the specification and I
 hope someone will come up with a way of fixing it someday.

I don't think it'll happen until preemptive concurrency is more widely
implemented.

 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.  It's really nice that we can use laziness to
 safely update a mutable value without blocking.  Another nail in the
 coffin for Standard ML.

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.

 I think the addForeignFinalizer function or whatever it is should
 nevertheless be renamed to addUnsafeForeignFinalizer (and likewise
 for newForeignObject).

I see some sense in that argument but:

1) I don't especially like that the only standard way of doing finalizers
   is labelled 'unsafe'.

2) We started cutting release candidates for Hugs yesterday using the old
   names.  Sigh...

Again, no strong objection but I'd do it differently.

 Also I suppose Alastair's hs_freeStablePtr function which allows you
 to do it from C, or whatever, will have to be added.

I've just added 

  void hs_free_stable_ptr(HsStablePtr x);

to Hugs in the hope that it will make it into the next release candidate

The capitalization change is for consistency with 

  void hs_perform_gc(void);

and I hope it will be what we put into the FFI report.

 I hope Alastair will forgive me for engaging him in such a lengthy
 argument, when he turns out to have been right all along.

I wish I'd come up with convincing arguments faster.

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



Re: The Revenge of Finalizers

2002-10-21 Thread Alastair Reid

 The problem is that the G-machine optimizes away some of the
 updates which make sure that the heap is always in a consistent
 state in a pure graph-reduction system.

 A pure G-machine updates all redexes, but the STG-machine only
 updates /shared/ redexes, yes?

It's a while since I looked at it but, IIRC, a naive graph reducer can
update the same redex multiple times while the G-machine tries to
update it just once.

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



Re: The Revenge of Finalizers

2002-10-18 Thread Alastair Reid

SimonM:
 My impression is that the problem is more fundamental: the thunk for
 x is under evaluation when the finalizer begins to run,

Urgle.  

 probably we shouldn't get a crash, but a blackhole instead.

Even a blackhole is wrong.  There's no cycle so it ought to evaluate
successfully.

 Fixing it so that the evaluation of x is actually continued is what
 we want, but I can't see an easy way to do that.

I think GHC does the right thing (semantically) here.  From memory,
GHC works like this:

  on entering thunk: turn it from a thunk into a blocking queue
   (optimization: delay the transformation until context switch time)

  on entering a blocking queue:
   if cyclic structure (i.e., already under evaluation by same thread),
 report blackhole.
   otherwise, put this thread to sleep on the blocking queue.

Based on this, what does GHC do here when a finalizer tries to
evaluate a thunk already being evaluated?  The finalizer is put to
sleep until the main thread finishes evaluation of the thunk.

And what does GHC do if a call to unsafePerformIO hits a thunk already
under evaluation by the same thread?  This is a blackhole (i.e.,
deadlock).  The thread throws the blackhole exception.


I think Hugs should report a blackhole in the unsafePerformIO case
(I believe it does already).

Hugs (and NHC, I believe) have no way to block finalizers once they
start executing.

I think our only choice is to turn off blackholing, allow the shared
term to be evaluated twice over and hope that the two updates to the
thunk (one by finalizer and then one by the main thread) don't do any
harm.  I don't know if this would work.  Even if it does, it's not too
palatable because of the loss of sharing and the space leaks (that
blackholing normally fixes).

 I suppose you could suspend either the finalizer or the main thread
 using the trick of saving its stack on the heap - is this
 implemented in Hugs?

No - it is an STG-specific trick.  Hugs is based on the G-machine.

In Hugs, the state of a pure evaluation is stored on the C stack and
in the heap.  We could try longjmp-ing out of the finalizer and hope
that the heap has a full and consistent record of the state but I'm
not overly confident that this would work.  (Hmmm, longjmp-ing out is
what exception handlers do and we believe that those work)

 The only other solution I can think of is to delay finalizers until
 we get back up to the IO monad.  

and not inside an unsafePerformIO call.

--
Alastair

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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

Alastair:
   On a system where finalizers behave like preemptive threads
 [nonsense deleted]

My outline of consequences/ implementation for GHC-like systems was
completely wrong because I was still thinking about finalizers as
special cases.

What needs to happen on GHC-like systems is that runAtomically takes a
global lock (just a plain lock, not a reader-writer lock) when it
starts and releases that lock when it ends.  Finalizers don't do
anything special when they start or end and they don't get blocked in
any special way.  Finalizers just take and release the lock the same
as anyone else.

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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

Alastair:
 So, is this a design that we could agree on?

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

Ok, onto the second question:

  Can we use atomicModifyIORef to make our code finalizer-safe?


I see potential problems wherever two IORefs need to be modified
atomically.  Obviously, it's easy enough to change code like this:

  foo :: (IORef a, IORef b) - IO ()
  foo (ref1,ref2) = do
modifyIORef ref1 f
modifyIORef ref2 g

to

  foo :: IORef (a,b) - IO ()
  foo ref = do
modifyIORef ref (f `cross` g)


More difficult would be something composite objects where multiple
IORefs need to be updated 'at once'.  With MVars, you'd use a single
MVar as the lock for the whole object and then use IORefs for mutable
bits within the tree.  You'd use a similar approach with a construct
like blockFinalizers.  I don't know how to achieve the same goal with
atomicModifyIORef.


--
Alastair

ps While pondering the problems in the semantics of blockFinalizers, I
came up with an alternative semantics which would make sense for GHC.

  @runAtomically m@ runs m atomically with respect to any finalizers
  or any threads also executing @runAtomically@.  That is, any side
  effects from m must not overlap with the side effects of any other
  finalizer or thread (if other threads exist).

  On a system where finalizers behave like interrupts (i.e.,
  finalizers can preempt normal threads and finalizers run to
  completion before any other finalizers or normal threads run),
  runAtomically has the effect of delaying execution of finalizers
  until m completes.  In the presence of cooperative concurrency, 
  we must also block execution of normal threads while m runs.

  On a system where finalizers behave like preemptive threads
  runAtomically must wait until all [other] currently running
  finalizers terminate and any other thread running rnuAtomically to
  terminate, then fresh finalizers must be prevented from starting
  while m is running, when m completes, any pending finalizers can be
  started.  (I think this can be implemented using something like a
  reader-writer lock where all finalizers must take the 'reader' lock
  when they start and runAtomically takes the 'writer' lock when it
  runs.  There's a small wrinkle on the standard reader-writer design
  that a 'reader' become a 'writer' if it calls runAtomically.)

  On multiprocessor systems, it might be possible to optimize things by
  taking the 'reader' lock only when the finalizers/threads start to
  have side effects.

I feel more confident that runAtomically could be used to make
libraries finalizer-safe than I do with atomicModifyIORef.




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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

Alastair:
  I don't know how to achieve the same goal with atomicModifyIORef.
 
George:
 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 must be missing something because this seems to be riddled with race
conditions.

In particular, if ioRef1 is updated by a lazy function, then the write
to ioRef1 happens but the write to ioRef2 does not.  

--
Alastair

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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

Ross Paterson [EMAIL PROTECTED] writes:
 there's an unsafe use in evalName(), 

I think this is easily fixed by using malloc to allocate the buffer
and then tracking down all uses and calling free.

 and I don't understand the mutual recursion between eval() and run().

Not sure what you don't understand here so let me sketch my understanding:

  eval traverses the graph looking for the next redex and then calling 
  an appropriate C function to apply the reduction.  One of these
  reducers is the bytecode evaluator 'run'.

  run evaluates bytecode which both constructs fresh bits of graph and
  implements the evaluate/test part of case expressions.  When
  evaluating case expressions, it has to trigger evaluation of the 
  selector which it does by calling 'eval'.

Without studying the code in detail, I believe that this recursion is
safe because run is a critical part of non-monadic evaluation - if
there were problems here, we'd have found them a long time ago.  Of
course, this naive belief might be shattered if I were to actually
look at the code in detail.

--
Alastair

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



Re: Objections to runAtomically

2002-10-17 Thread Alastair Reid

 However we don't really need to discuss this anyway, since I don't
 think either runAtomically or atomicallyModifyIORef need to be in
 the FFI standard.  I'm quite happy to leave this open.

As usual, I disagree.  I think the FFI spec would be incomplete if it
provided Haskell finalizers but no mechanism to write them safely.

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



Re: Objections to runAtomically

2002-10-17 Thread Alastair Reid

 I don't like runAtomically either, because once again it assumes a
 global lock.  

It has to be a global lock if we are to implement it on NHC and Hugs.
Since we can't block finalizers once they start running, the only way
to get atomicity is to stop them running.  This requires use of a
global lock unless we had (in advance, before the finalizer starts
running) a list of the set of objects that the finalizer is going to
access.  It'd be hard to do this while treating libraries as black
boxes.

 This is fine for GHC or Hugs or NHC on single processors, but it
 would be a pain if you had multiple processors.

By 'pain' you mean slow?

Since  90% of uses of runAtomically will be with modifyIORef, we can
avoid this overhead by providing atomicModifyIORef in the IORef
library as well.  Multiprocessor GHC is free to implement it more
efficiently if necessary/ convenient.

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



Re: Objections to runAtomically

2002-10-17 Thread Alastair Reid

Alastair:
  Since  90% of uses of runAtomically will be with modifyIORef, we
 can avoid this overhead by providing atomicModifyIORef in the IORef
 library as well.  Multiprocessor GHC is free to implement it more
 efficiently if necessary/ convenient.

 [snip] I'm not convinced the overhead is going to be all in
 modifyIORef. 

If you don't believe that runAtomically is necessary, you can't
believe that we will ever call it.  That being so, the performance
overhead shouldn't concern you.  (Implementation effort would be a
different kettle of fish.)

 For one thing runAtomically once again assumes the existence of some
 linear ordering on all state operations performed by the program.

It assumes that side effects can be linearized.  Every theory of
concurrency I know of makes the same assumption.

 I don't have any experience of programming for
 multiple processors so I don't know what repercussions it would have
 for the run-time system, but it seems possible that there would be
 some, even in stateful operations which have nothing to do with
 runAtomically.

The only repercussion in a multiprocessor system is that calls to
runAtomically must take a global lock.

Global locks have been implemented enough times that the issues have
been figured out many times.

 Of course it will be possible, but since Alastair seems to be happy
 for the IORef to contain atomicModifyIORef anyway, I don't see a
 pressing need for the additional primitive.

The need is for the small number of cases where the state is spread
over a number of mutable variables (IORefs, maybe some mutable arrays,
maybe some C state) and we want to update it atomically.

Even if George's unsafePerformIO trick is correct (I remain doubtful),
its unlikely that Joe Haskell User will apply the trick correctly so
it's better to provide them with a simple alternative.

--
Alastair

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



Re: Objections to runAtomically

2002-10-17 Thread Alastair Reid

 Since we've talked about mutable state quite a lot, my suggestion
 would be that we write, in addition to the FFI specification, a
 Mutable State specification which documented newIORef, readIORef,
 writeIORef, atomicModifyIORef (and possibly, for reasons of
 efficiency, atomicModifyIORef_).  I don't think it need be very
 long.  It wouldn't have to be frozen right away; it would be good if
 some other working group could be formed to carry it further, so
 that for example it could also include mutable arrays.

It's already stable, well documented, etc. (and has been for something
like 6 years now).  We can reformat the Hugs-GHC library docs into
Haskell Report style and give it the official Haskell committee seal
of approval if it makes you feel any better but the spec won't change
at all in the process so it doesn't alter any of the questions
currently on the table.

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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

 However in general I think we can hide some of the horribleness from
 the user:

 modify2IORefs :: IORef a - IORef b - (a - b - (a,b,c)) - IO c
 [horrible code deleted]

And if they need to update 3 IORefs or a list of IORefs?

Writing code like that yourself and getting it right and portable
between compilers seems to be ludicrously hard.

I can't tell if that code is right (my gut says no).  Worse though, I
don't even know what semantic framework to use to reason about it if
we want to be sure the code will work in the presence of strictness
analyzers, eager evaluation, parallel evaluation, fully-lazy
evaluation, etc.  Operational reasoning and reasoning by example
struggle with such a task.

--
Alastair


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



Re: Objections to runAtomically

2002-10-17 Thread Alastair Reid

 Could we not at least replace the global lock by a local one?

I refer the honourable gentleman to my previous answer.

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



Re: The Revenge of Finalizers

2002-10-17 Thread Alastair Reid

 Worse though, I don't even know what semantic framework to use to
 reason about it if we want to be sure the code will work in the
 presence of strictness analyzers, eager evaluation, parallel
 evaluation, fully-lazy evaluation, etc.  Operational reasoning and
 reasoning by example struggle with such a task.

 However the main assumption that is being made by
 the code I gave is that the thunks containing the unsafePerformIO's
 do not get multiply evaluated.  I think this is a reasonable
 assumption to make.  I am not scared by any of the buzzwords you
 give.  

The essence of all those is that they have been implemented for
Haskell and that they either change evaluation order or increase or
decrease the number of times expressions are evaluated.

Most of them have non-local effects: by analyzing how a function is
written, we can decide to treat the argument differently.  The
compiler can do this because the typesystem tells it the code is pure.
Uses of unsafePerformIO may result in the typesystem saying something
is pure when it is not but in those cases, the blame lies with the
person who used unsafePerformIO for writing the code (that's part of
the spec of unsafePerformIO).

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



Re: Why I want Haskell finalizers

2002-10-16 Thread Alastair Reid


George writes:
 If you have Haskell talking to some
 other language with a garbage collector, be it Java or SML, then at
 a given point of the program you can in general expect to have
 Haskell holding stable pointers to objects referenced from their
 world by the other language, and vice-versa.  The most obvious way
 of garbage-collecting these is for each language to reference the
 foreign objects using its own version of ForeignPtr's, which then
 instruct the other's RTS that the corresponding stable pointer is no
 longer required. 

So what you want is for the Java GC to call hs_freeStablePtr on all the
Haskell objects that just died?

That requires that the Haskell runtime system export a C function
hs_freeStablePtr which fiddles around with the relevant GC data
structure for stable pointers.  No problem at all.  Hugs has exported
this function for some years now (though under a slightly different
name).

Similarily, you want Haskell's GC to call a function in the Java
Native Interface (JNI) to release any Java objects that Haskell may
have.  I imagine that is straightforward.

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



Re: The Revenge of Finalizers

2002-10-16 Thread Alastair Reid


 (2) blockFinalizers looks fine for Hugs and NHC which only have a
 single-thread model, but it looks tricky in general where [...]

Ah, I see what you mean.  

I'd kinda hardwired into the definition the assumption that finalizers
run at higher priority than other threads and that there's a single
execution thread.

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?  

It seems a reasonable question to ask is whether either PVars or
atomicallyModifyIORef could be used instead of MVars in existing
concurrent code.  If yes, then it seems likely that we can make our
libraries Finalizer-safe.  If no, it'll probably give us some clues as
to what is missing and we can think about whether we'd miss them.

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



Re: Why I want Haskell finalizers

2002-10-16 Thread Alastair Reid


 So what you want is for the Java GC to call hs_freeStablePtr on all
 the Haskell objects that just died?

 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.

 If you want any slightly more complicated logic
 (such as if Java has multiple references to the same StablePtr, or
 if you want to detect if this particular freeStablePtr might free a
 circular data structure) you'll have to write it in C.

As you know, I'm not against writing finalizers in C :-)

Seriously though, I think detecting circular data structures requires
more than just a cool C (or Haskell) library on the Haskell-Java
interface.  I think it requires at least one but probably both GCs to
provide hooks so that the GCs can get some sense of what Haskell roots
are keeping what Java roots alive and vice-versa.  (Every time I think
about this problem, the word 'epoch' comes to mind...)

--
Alastair


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



Re: The Revenge of Finalizers

2002-10-15 Thread Alastair Reid


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

No.

And my recent focus on IORefs has simply been because they seemed the
strongest argument.

A

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



Re: Finalizers strike back

2002-10-12 Thread Alastair Reid


 (It would be nice to have some concurrency in nhc98, of course, but
 I don't foresee that happening soon.)

I remember implementing cooperative concurrency in Hugs as being
rather easy.  Of course, that was building on a base which already used
a continuation passing IO monad...

If you want to try, I could dig out some details but the main issues
are:

1) When you have a choice of which thread to wake next, it matters
   which you wake next.  IIRC, waking the wrong one makes it impossible
   to implement a producer-consumer pattern.

2) There's a lot of interaction with non-deterministic exception
   handling.

3) unsafePerformIO foo had better not block since we have no way to
   block the non-monadic code that invoked it.  In that case, we 
   raise an exception or give up (don't remember which).


 Actually, I'm just wondering whether I can use the GC as a
 poor-man's scheduler.  If a finaliser blocks on an MVar, save its
 state, keep the finaliser in the pending queue, and return to the
 main thread.  Then on the next GC, try the same finaliser again, ad
 infinitum until it succeeds.

The finalizer won't become runnable until someone does a putMVar so
you can deal with this case by storing the finalizer's state in a
queue of blocked threads attached to the MVar and having putMVar do a
context switch to the thread at the head of the MVar's queue of
blocked threads.  If you want finalizers to have priority over other
threads, have two queues: one for finalizers, one for normal threads.


--
Alastair

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



Re: The Revenge of Finalizers

2002-10-12 Thread Alastair Reid

 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

[The last sentence is to take care of cases like finalizers calling
blockFinalizers.]

One would then write George's example like this:

 updatePVar (PVar ioRef) updateFn = blockFinalizers $ modIOVar ioRef updateFn 

This is what I was referring to the other day when I suggested that a
mechanism in the style of interrupt disable might be easier to
implement than MVars.


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



Re: Finalizers Ride Again

2002-10-12 Thread Alastair Reid

 [snip] I don't see that it's necessary for us to come to a decision
 right now about PVars unless we want to put them in the FFI
 standard.  

But what if we can't agree on something like PVars or we decide that
Haskell finalizers plus yet another synchronization mechanism is worse
than C finalizers?

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



Re: Finalizers 2: Bayou Justice (and Weak pointers to boot...)

2002-10-12 Thread Alastair Reid

 For the record, I am strongly in favor of Haskell finalizers, if a
 Mutable State extension were to be written, then it will have to
 address the issue with one of the solutions mentioned in this
 thread, 

We already have a perfectly good Mutable State extension.  We know
exactly what it looks like.  It's already implemented by all compilers
that support the FFI.

There's really no question of putting off solving FFI-induced problems
until such an extension exists.  The extension exists now, the problem
would have to be solved now.

 The ability to tie the liveliness of ForeignPtrs together is quite
 important for many applications.

Can you give an example?  (Maybe there's a paper that mentions it,
I'll happily go read that.)

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



Re: Finalizers etcetera

2002-10-11 Thread Alastair Reid

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

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

I guess I can imagine doing it - but not often.

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

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

This works with preemptive concurrency because whilst we don't know
when it will run, we do know it will run.  In fact, we can estimate
when it will run: if there are N threads in the system and timeslices
are t units long, they won't be delayed more than N*t.  If this delay
is too long, the timeslices can be made shorter (I think GHC has a
switch to do this).

With Hugs' cooperative concurrency, context switches can be delayed
indefinitely.  They can be delayed because the program is executing
pure code.  They can also be delayed because, though in the IO monad,
they do not hit a context-switch triggering event.  Especially in
single-threaded programs, there may be very few context-switch
triggering events.  One could easily see the program run to completion
before the finalizers have a chance to run.  There's no equivalent to
making timeslices shorter that will make the situation better.

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

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

There has to be _something_ we can rely on about finalizers.  

If my programs have to work even if finalizers never run, I could make
life much simpler for myself by not bothering with finalizers.  We
know that won't work though.  

I find the idea of switching from a design where finalizers are run
promptly to a design where they may be delayed for a long time or
never run at all highly unsatisfactory.  

 So the question before the house is to choose between:

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

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


 I still prefer (A), albeit not unto death, because 

I prefer (B) because:

1) it doesn't require us to implement concurrency in order to call C
2) it satisfies the FFI goals of letting us finalize foreign objects
3) finalizers can be run promptly
4) implementation is straightforward


 (i) I believe that supporting MVars in Hugs is not as hard as you
 think.  

I think it is terrifically hard to implement this unless we are
willing to delay execution of the finalizers until we are back at the
IO level (inside a call to unsafePerformIO wouldn't count).  (In case
there's any doubt, I am strongly against delaying their execution
indefinitely, requiring the programmer to regularily pop out to the IO
level, etc.)

What disturbs me is that when GC strikes, the currently executing
thread doesn't have a properly constructed continuation which can be
saved on the ready list.  Instead, its execution state is on the C
stack and there's no convenient way to save that away.

[Just in case it's not clear from last night's description of Hugs'
concurrency: Hugs carries around a continuation only for stuff in the
IO monad; it uses the C stack when executing pure code.  Also, my
trick for stripping state off the stack and into a chain of stack
frames stored on the stack is only for the STG machine, not Hugs.]

 (I'm agnostic about NHC.)

We'd better get an opinion on that soon because everyone but me seems
to be going for a design which needs a way for the main thread to
protect against finalizers (without disabling GC, of course).  [I use
vague language to describe this protection because I guess it's
possible we could go for a simpler kind of lock than MVars which, on
Hugs and NHC, would protect the main thread from preemption by
finalizers but not vice-versa.  More like disabling interrupts than
locking.  I haven't thought through all the details but it might be
simpler.]

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

The way I see it C finalizers avoid portability problems.

If I ask 100 Haskell programmers to write C finalizers, I'll bet 95%
of them will not even think of calling Haskell from inside 

Re: Finalizers etcetera

2002-10-10 Thread Alastair Reid


 I don't think = is frequent enough.  Pure code that manipulates
 big C objects (remember that image processing example of mine?) can
 generate a lot of garbage C objects without once going into the IO
 monad.

Also, thanks to unsafePerformIO, = can be invoked during execution
of a primitive even if the arguments of the primop do not involve IO.

This is somewhat beside the point though - the main worry is about
race conditions in user-written code.

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



Re: Finalizers etcetera

2002-10-10 Thread Alastair Reid


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

I claim that the major thing that finalizers do is manipulate shared
state.  Their task is to clean up when an object dies and the reason
we care whether or not that cleanup happens is that the thing being
cleaned is shared with live objects/threads.

If I want to manipulate shared C state, then finalizers written in C
do rather well.  I see no compelling need to write them in Haskell.
(And I see significant problems in encouraging people to write them in
Haskell.)

To get any benefit from writing finalizers in Haskell, I have to have
MVars which protect against finalizers.  Malcolm: are you ready to add
MVars to NHC?

 But there's something I'm puzzled about.  Hugs does support
 non-pre-emptive concurrency, right?  (Where can I find a description
 of it.)

I don't think I ever described it in print.

Mark Jones implemented the IO monad using two continuations:

an error continuation:   IOError - ()
and a success continuation:  a   - ()

On this base, I added MVars (whose state is either a value or a list
of success continuations) and a queue of running tasks.  Context
switches happen when you manipulate MVars and when a thread
terminates.

 So would it not be easy to implement (non-pre-emptive) MVars?

Yes, we have those.

Of course, NHC will have to add them too.  There's no reasonable way
to add Haskell finalizers without providing locking as well.

 And if they existed, everything would be fine, right?  We could
 just use Haskell finalizers as we all want.  Or am I missing
 something.

Finalizers would have to be scheduled by the same scheduler as normal
threads.  (This is the key change. SimonM's patch effectively set up
the garbage collector as a separate scheduler much as 'scheduling' of
CPU interrupts isn't handled by the pthread scheduler.)

The scheduler would need to prioritize finalizers over normal threads.
That is finalizers should be run whenever they are runnable.  This is
essential in cooperative schedulers because you never know when or if
a thread will give up control.

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

I think there's a bunch of other changes needed but it's way past my
bedtime - I'll need to think more about this.

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

That's pretty much it.

Of course, to get any benefit from restricting them to being written
in C, C finalizers have to be restricted to not call Haskell code.
(Calling the Haskell runtime isn't ruled out though some calls like
performGC may be off limits.)

And to get any benefit from allowing finalizers to be written in
Haskell, you have to have MVars.

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



Re: Finalizers strike back

2002-10-10 Thread Alastair Reid


 [snip] I'm not sure I really understand the problem.  The FFI
 standard (Release Candidate 4, the one I have printed out here) does
 not define IORefs, and of course Haskell 98 doesn't either.
 Therefore, although this code is broken, this particular example
 doesn't matter if all we are considering is code written in Haskell
 98 + FFI.

If there's no shared mutable Haskell state, writing finalizers in
Haskell buys you little - what does a finalizer do other than cleanup
shared state?  (Note that it doesn't cleanup unshared state - what
would be the point?)

I think IORefs are the most widely accepted extension of Haskell.  The
FFI spec doesn't depend on IORefs but it should certainly be designed
to work in an environment where they exist.

 However to me this code just looks totally wrong because of course I
 use GHC, a system with preemptive scheduling, and would regard it as
 incompetent to use anything other than an MVar here. 

I completely agree.

I do not believe we can have any useful form of Haskell finalizers
(meaning finalizers that manipulate shared Haskell state) without
adding MVars.

But, since concurrency is not so widely implemented as IORefs, we are
trying to produce an FFI design which does not require concurrency
extensions.

My solution to this conflict is not to add Haskell finalizers.

 However to me this code just looks totally wrong because of course I
 use GHC, a system with preemptive scheduling, and would regard it as
 incompetent to use anything other than an MVar here.  Even for Hugs
 I don't like this code, because [...]

I think you're taking my code out of context.  The purpose in writing
that code using IORefs was to show the kind of code you should not
write because it would suffer from race conditions.

I completely agree that some form of locking is required to make the
code safe. 

I guess I'd be willing to have Haskell finalizers if we agreed on an
appropriate form of locking that all implementers can and will
implement.

NHC currently lacks a locking mechanism.

I believe that using Hugs' MVars in conjunction with SimonM's patch
will lead to deadlock in the cases that would have suffered race
conditions using IORefs.

 Supposing we posit that there is a GlobalVariables standard.

Just want to remark that the variables don't have to be global.
Haskell finalizers are specified by closures and closures can point to
any IORefs you fancy.

 Anyone writing a finalizer should be aware (indeed the FFI standard
 should say) that the finalizer may be run at any point (after all,
 when else would you expect it to run) and should take precautions
 against it.  

What I hear you saying is that the FFI standard should depend on a
concurrency standard.  I think there was a strong sentiment that we
should avoid this.  I agree though that it is necessary if we allow
Haskell finalizers.


--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Finalizers etcetera

2002-10-09 Thread Alastair Reid


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

What is definitely a problem is the issue of atomicity of user-written
Haskell finalizers. 

--
Alastair

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



Re: addForeignPtrFinalizer

2002-10-03 Thread Alastair Reid


 To be honest, I don't understand why you are so opposed to this.

I don't want to encourage people to write code which can't work on
Hugs and NHC.  If we provide Haskell finalizers with the restriction
that they can only call C code, users will go ahead and write
finalizers which call arbitrary Haskell code and then the code won't
work with Hugs and NHC - portability is decreased. 


So, maybe we should make Haskell finalizers work as well on NHC and
Hugs as they do on GHC?  What would it take to do this?

I believe it would take a massive effort to make Haskell finalizers
work both for existing systems and new systems because:

1) Being able to write finalizers in Haskell is pointless
   unless they can safely modify shared state.  (Worse, it is
   dangerous because unsafely modifying shared state leads to 
   race conditions which are unbelievably hard to track down.
   Much harder than the debugging sessions that George envisages.)

   Any useful form of Haskell finalizer requires the provision of
   blocking synchronization which will require a complete rewrite of
   the runtime system and potentially decrease portability.


2) None of our Haskell primitives are intended for a multi-threaded
   environment.  Consider a pair of primitives that share a common
   data structure like hClose and open.  What happens if a finalizer
   calls hClose while the main thread is in the middle of creating a
   file?  It probably works ok but we know from experience with
   writing multithreaded code that the only way to be sure is to look
   at the code.

   In fact, we have to check it and every other Haskell primitive that
   affects some shared structure.  In other words, we have to vet a
   lot of code to see if it can be used in a single-threaded way and
   modify offending code by moving any allocations to the start or end
   of the modifications.

   We also have to keep this in mind every time we modify the 
   runtime system.

In short, we have to do most of the work of making Hugs support
preemptive concurrency: we have to provide blocking synchronization
and we have to rewrite our code as though a preemption could happen 
on any heap allocation.

Plus, it makes maintenance harder because it makes it easy to
introduce race conditions.


 Why not find out whether SimonM's patch works?  If it does, the
 problem is solved, we can use the nicer definition, and everybody is
 happy.

As you know, testing for race conditions is very hard.  We could test
and test and not see a problem and then a week into the release we get
a bug report.  But, worse, the report also says that the bug goes away
if they make some small change to their code.  The change will not
actually fix the problem, it will just change the allocation/GC
pattern so that the problem doesn't show up in the test.


--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: addForeignPtrFinalizer

2002-10-02 Thread Alastair Reid


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

This is a pretty large restriction since the only reason for running
Haskell finalizers is to manipulate shared Haskell state.  

Here's a typical example of where you would need Haskell finalizers
instead of C finalizers: consider a simple graphics library which
maintains a list of windows and deletes a window from the list when
its finalizer runs (it presumably uses weak pointers to avoid the
space leak).  If the finalizer blindly deletes the object from the
list, we get a race condition.  If the object is protected by a lock,
the finalizer can't access it.  If we want to allow finalizers to
access objects protected by a lock, we have to be prepared to block
execution of the finalizer until the main thread releases the lock.

I claim that Haskell finalizers are no use unless we provide
synchronization primitives, those primitives are able to block
execution of a currently running finalizer.  I also claim that
implementing blocking is a significant undertaking.

Simon's patch doesn't make Hugs' concurrency implementation work with
finalizers and it will take a fairly significant rewrite of the
implementation to make it work.  (At present, it doesn't work with
unsafePerformIO.)  I don't know if I'd be able to support blocking 
in any useful way without reimplementing the whole thing on top of
a native thread library (pthreads, etc.)

AFAIK, NHC does not implement any concurrency primitives so NHC would
have to add them before it can provide any useful form of Haskell
finalizers.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

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



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

2002-10-01 Thread Alastair Reid


 I agree that it's extremely unsatisfactory, but it seems the best
 option (to me) of defining it is not going to be accepted.  So at
 least it would be better if GHC's documentation said We implement
 the FFI while Hugs and NHC's said We implement the FFI with the
 caveat that finalizers may not call back into Haskell, as specified
 in section [blah]. 

I maintain that it is better to specify something simple and for GHC
to document that it goes beyond the specification just as it does for
unboxed types and the like.

What's the point in going to all the effort of coming up with a common
specification, all of us hacking our implementations to match the
spec, endless arguing over details of the syntax, types, libraries,
etc. if it doesn't achieve the goal of improving portability?  It
would have been much easier if we'd left our (incompatible)
implementations alone and not made an effort at defining a portable
ffi spec.

  Since I regard this caveat as an extremely
 important one (for example, it severely limits the use of the FFI to
 link to languages like Java, which also have their own GC) 

I just want to note that I believe what you really need is a bunch of
entrypoints into the runtime system not the ability to call Haskell
code.

 it needs to be stated very clearly in the documentation of those
 implementations which have it, rather than being left as an
 embarassing hole which the user will only discover after a long and
 painful analysis of the core-dumps.

Note that the problem is _exactly_ the same problem faced when using
foreign functions which were declared using the 'unsafe' calling
convention.  The only difference I can see is that unsafe calls are
much more common so they are more of a problem.

As I was implementing the unsafe stuff in Hugs, it occurred to me that
I could probably dynamically detect when an unsafe function (i.e., one
which the user promises is not reentrant) performs a reentrant call.
The idea is that on making an unsafe call, we set a bit saying that
reentrancy is not allowed and on calling into a foreign exported
function or performGC we check whether the bit is set.  Making this
work in a multithreaded setting like GHC would be more painful and
more expensive but probably feasible. 

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: addForeignPtrFinalizer

2002-10-01 Thread Alastair Reid


 I have to say that, given Simon's patch, I am inclined to revert
 back to the old API for foreign pointers.  

I don't think such a change should be made unless Malcolm and I are
able to implement it.  

I'm not yet convinced that Simon's patch is as easy or correct as it
seems and will not be until it has been heavily tested and until I
have a chance to look carefully at the consequences of the change
elsewhere in the system.  

Also, Malcolm reported using a similar trick but that he couldn't get
it to work reliably (i.e., it was ok if the finalizer did nothing but
call out to C but not otherwise).

 The restriction on pure C land finalizers *is* awkward, and as we
 have already seen implies further changes (ie, adding something like
 `finalizerFree').

We missed a small detail in specifying the change and fixed it when we
went to implement it.  This happens with most design changes and
doesn't seem like evidence of awkwardness to me.


--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: addForeignPtrFinalizer

2002-09-30 Thread Alastair Reid


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

I don't think it's appropriate to add that burden just so we can call
free at the right time.  We have a simple problem, there should be a
simple solution.

A


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



Re: addForeignPtrFinalizer

2002-09-26 Thread Alastair Reid


 Still hoping ;-) The discussion seemed to stop without reaching a
 conclusion last time.

I thought it was concluded and the report changed such that all three
compilers which implement the ffi spec can implement it without
receiving a heart, lung and liver transplant.

 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.

We've written a bunch about it.  I suspect that if we were to give a
full and complete list of all the changes required we'd have done most
of the work required to implement it (though not the work to debug and
maintain it which is probably more significant).  We're not going to
do that so you'll have to live with the explanations we've given so
far.

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



Re: addForeignPtrFinalizer

2002-09-24 Thread Alastair Reid


Alastair wrote:
 I seem to remember that Sigbjorn and Erik dealt with this problem by
 arranging some kind of GC-visible link between the objects so that
 until the second finalizer has run, the object will not be
 considered garbage.

Sorry, this was nonsense - I hadn't noticed that is was a single
ForeignPtr (in Haskell land) as well as being a single object (in C
land).

Seems like it'd be reasonable to specify an order for these.

An alternative would be to drop addForeignPtrFinalizer.  I have no
idea what the motivation for this function is since I can't think when
you'd need/want/prefer to add finalization actions incrementally
instead of doing it in one step.  Can someone give a motivating
example where there is some advantage in adding finalization actions
incrementally?

--
Alastair

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



Re: lightweight struct handling in FFI?

2002-09-19 Thread Alastair Reid


I made a start on writing an FFI howto at:

  http://www.reid-consulting-uk.ltd.uk/docs/ffi.html

It is very rough, doesn't answer your specific question, has many
typos and omissions, etc. but some of the links in the Tips and Tricks
section (section 4) might help.  


To answer your question directly, I think it all depends on what
you're doing.  

Sometimes the semantics of the operations make it easy.  For example,
if there is any notion of object identity (and it often isn't stated
whether there is or not), you usually have to keep the master copy in
the C world and not duplicate.

If there is no notion of identity, no modification to the object,
etc., it is often easiest to keep it on the Haskell side and copy over
to the C side on each operation because it's easier.  There may be a
performance hit in doing this depending on the number of times it is
copied in each direction but I don't think we have any numbers for a
range of implementations (ghc numbers may be available).

Without any effort at measurement, I'd say that using malloc is pretty
slow (because C's malloc is pretty slow) and that ForeignPtr's are
fairly low overhead but more than just copying a small object over.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
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 Alastair Reid


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

That's fine and, of course, it can be implemented that way.

I guess the issue is that if someone wanted to use MarshalAlloc.free
as a finalizer they would not be able to do so.  Since we don't
guarantee that MarshalAlloc.malloc is stdio.h malloc, they couldn't
portably cons up a compatible free.

The relevance to mallocForeignPtr and friends is only that I happened
to notice the problem while implementing them.

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



Re: Updates to FFI spec

2002-09-13 Thread Alastair Reid


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

Marcin:
 OCaml allows the programmer to specify an approximate amount of
 foreign memory in its wrapped C pointers. Maybe it's a good idea?

We did that on the C/C++ side of things so that we could keep track of
how much image memory was in use and try to trigger a GC when the
amount of memory was significantly higher than the running average (or
some such).

I wonder why OCaml would do it on the Caml side?  

Maybe they include similar heuristics but as a standard part of the
system instead of leaving it to each library writer to roll their own?

Or could it control the amount of GC performed?  If you know that all
the objects you care about are in the youngest generation, you could
decide to collect just the youngest generation.  (Except that isn't
always enough - releasing an object in the old generation might
release a pointer into the new generation.)

--
Alastair

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



Re: Proposed change to ForeignPtr

2002-09-11 Thread Alastair Reid


 BTW, having two languages with separated heaps interact is a big
 mess as soon as you can have cycles, which you usually cannot
 exclude.  Alastair already pointed that out and Martin Odersky also
 has nice stories to tell about this.

Hmmm, way back in '94, my thought was that the only thing to do in the
presence of these cycles was to run the two GCs at once with a rather
intimate communication between them where one says 'I can reach X' the
other says 'ok, now I can reach Y', and eventually they both run out
of objects to trace and they can discard unreached objects.

The problem with this is that it runs into the same problems Malcolm
and I are so keen to avoid: the other language has to be able to
trigger GCs at more or less arbitrary times.

Since then, I've read a lot about non-stop concurrent GC which doesn't
need the two GCs to run simultaneously.  Just thinking aloud, I wonder
if it would be any easier to implement?  The communication would be
much the same ('I'm starting', 'I can reach X' and 'I'm done') but 
there'd be no need to synchronize the GCs.


-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

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



Re: Updates to FFI spec: performGC

2002-09-11 Thread Alastair Reid


 Do you want a stronger wording on what kind of garbage collection is
 to be performed or do we want to keep it deliberately unspecified
 (ie, leave it to the individual Haskell system)?

It'd be nice to say that it has to be a full GC - but I've no idea how
to specify that in a non-operational (i.e., implementation dependent)
way.  We could insert the word 'full' and leave it to people's
imaginations?

-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/


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



Re: Updates to FFI spec: performGC

2002-09-11 Thread Alastair Reid


Alastair wrote about performGC (snipped)
 It'd be nice to say that it has to be a full GC - but I've no idea
 how to specify that in a non-operational (i.e., implementation
 dependent) way.

George Russell [EMAIL PROTECTED] writes:
 I certainly don't think you should constrain implementations to be
 able to perform a full GC in any sense.  It is possible if
 unlikely that someone will get along to implementing the
 HaskellKit, where GC is entirely dispensed with and replaced by
 region analysis.  Even if that's not the case, I certainly hope that
 one of these days someone will get along to implementing a Haskell
 compiler that does at least some easy region analysis.

Region-based systems have the quite wonderful property that garbage is
disposed of promptly - you don't have to wait for the next GC for the
memory to be released.  Which means that performGC becomes a nullop.

[That said, I'm not sure that region-based analysis is all that easy
in the presence of lazy evaluation since it is so critically tied to
estimating lifetimes.]

 Also there are probably hard-real-time GC algorithms (like Baker's
 treadmill) or algorithms which are close to being hard-real-time
 (like the train algorithm) where doing a full GC would be a major
 pain.

The desired property is that the runtime system releases all
unreachable objects.  

To make the fine-grained GCs (i.e., those that do a little GC now and
then instead of a full GC) do this, all you need is stop mutating or
allocating objects and then keep invoking the GC until it gets round
to where it was when you started.  There's usually some kind of
colouring or 'epoch' mechanism that lets you know when you're back
where you started.

Of course, you trash any real-time properties in the process - see
recent mail by me in the archive or my old paper for ideas on how to
lessen that or dream up your own ideas for how to make two real time
GCs work together nicely.

[Again, though, I'm not sure there's much danger of a RT GC being
added to Haskell - it's too hard estimating execution time, memory
usage, etc. so making your GC more predictable doesn't seem like a
major win.]


In short, I think the current design is perfectly adequate for
interfacing current systems to C code and will extend nicely in the
future as motivating examples make actual needs.  For example, even if
we had a finer grained version of performGC, I expect most people
would find that performGC provided the functionality that they need so
they'd write their own (using a finer-grained interface) if we didn't
provide it for them - only those who have real time programs
interfacing to Haskell would make use of the finer-grained interface.


-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

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



Re: Updates to FFI spec: performGC

2002-09-10 Thread Alastair Reid


I think the thing to do is add the existing performGC to the standard
(perhaps giving it an hs_ prefix in the process) and leave development
of an extended version of the function for when the GHC folk (or
anyone else with a generational collector) decide they want a
forcefulness argument.  Come that day, we'd define:

  void performGC(void) { performPartialGC(0); }

(or whatever it is you do to force a full collection).

A

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



Re: module Data.Bits

2002-09-10 Thread Alastair Reid


 Errm, but in C there is no unified shift operator.  You have  for
 left shift and and  for right shift, and a negative shift is
 undefined.

[blush]

 This makes the specification come out nice and clean - you're
 multiplying the number by 2^n instead of 2^{-n}.

 Errm, but then right shift comes out as dividing by 2^{-n}, instead
 of 2^n.  For a unified shift operation, I don't think there is any
 good reason to prefer one direction over the other, since there is
 no precedent in another language (AFAIK).

I think this spec (for 0 == left shift)

  shift x n = x * 2^^n

is simpler than (for 0 == right shift)

  shift x n = x * 2^^(-n)

[Ok, I probably need a few from/to Fractionals added to those specs]


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



Re: Proposed change to ForeignPtr

2002-09-10 Thread Alastair Reid


 I think this is all a rather murky area.  Consider two systems,
 let's call them Haskell and Foogle, which both operate heaps and do
 their own storage allocation, but also communicate over similar
 FFIs.

This is indeed a murky area.

Especially tricky when you have two GC's (even if one is nothing more
than reference counting) is the issue of cycles that span the two
systems: neither side is willing to release its pointer into the other
world until the other side releases its pointer.  (See section 5.2 of
http://www.reid-consulting-uk.ltd.uk/alastair/publications/FP94.ps.gz
for more on the problem and a sketch of a fix.)

 We might very reasonably have situations where fairly complex
 inter-language pointers exist, so for example Haskell holds a
 ForeignPtr to something in the Foogle heap; the pointed-to Foogle
 object in turn references a Haskell object (presumably provided via
 StablePtr).  Now suppose Haskell wants to drop the ForeignPtr.  Then
 the logical thing for the finalizer to do is to tell Foogle that
 Haskell is no longer interested in the Foogle object.  This then
 gives Foogle the chance on its own garbage collection to in turn
 drop the Haskell StablePtr.  In turn this means somehow running
 StablePtr.freeStablePtr.  However this scheme I don't know if that's
 legal, because the Haskell finalizer you need to run freeStablePtr
 is indirectly provoked by the initial Haskell finalizer.

We should provide a C function hs_freeStablePtr and explicitly
say that it is safe to call this from inside a finalizer.

 Of course you would need at least reference counters (if you can
 guarantee there are no cycles containing both languages) or
 something more powerful otherwise, but reference counters at least
 can be provided. 

At least half the times I've used ForeignPtrs (aka ForeignObjs aka
MallocPtrs), I've had to implement my own reference counting so, yes,
it does seem like it'd be good to include reference counting in the
implementation somehow.  

I don't remember ever finding a good way to do it though.  The design
seems obvious enough but it seems there's always some odd little
wrinkle like the object already having its own reference counting
implementation or the other world wanting to talk about foo_t* (i.e.,
the type the external library provides) instead of hs_stablePtr_t.  In
particular, if I put a wrapper around an object so that I can attach a
reference counter, you somehow always find yourself faced with the
problem that a C library hands you a pointer to an unwrapped object
and you have to try to track down the reference counter for it.

Any ideas welcome.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposed change to ForeignPtr

2002-09-10 Thread Alastair Reid


 [snip] No, you do not really need separate threads for this problem
 to occur.  All you need is, say, Hugs to call a GHC-exported
 function as a finalizer, in the same OS thread, GHC to run a garbage
 collection during this function, and the garbage collection in turn
 to want to run a Hugs finalizer, before the finalizer called from
 Hugs has finished. 

The Hugs and GHC runtimes can talk to each other just fine (or, if
they can't it's a simple oversight and well fix it).

There's no problem with GHC and Hugs each telling each other that some
object they own has one less pointer to it.  Next time it is
convenient for the runtime, it can run a GC, perhaps recognize that
there's a few GHC objects it can release and it tells the GHC runtime
that it can release them.

The reason we can do this is because it has limited scope: just a few
data structures have to be tweaked to avoid GHC coming in when Hugs'
data structures are in an inconsistent state.

It's quite a different matter to allow arbitrary Haskell code to be
run - that means the entire runtime system and libraries have to be
made reentrant.

 Of course one wouldn't normally want to link GHC
 from Hugs, but if even these two cannot be made to meet, I don't
 know how you expect Haskell to call anything else with a reasonably
 flexible GC system; it puts the kybosh on Java for example, which I
 am fairly sure makes plenty of use of both callbacks and finalizers.

That's fine, they can have all the finalizers they want.
The finalizers can fiddle with things in the runtime system
to tell the GC whatever they want.

 In any case it seems to me just as dangerous to assume that the
 implementation does not use OS threads, as to assume it does.

The internal structure of your apps is up to you - use locks to avoid
using single-threaded code in multithreaded manner.

 You are effectively writing on top of the FFI document If your
 program does this perfectly reasonable combination of finalizers, it
 will fall over in an undefined way should the implementation use OS
 threads; furthermore there is no way around this.  Basically the
 fact that there is only one OS thread is an implementation detail,
 not something that the user should have to think about.

Programmers are used to dealing with code which is single threaded or
not reentrant.  It's quite common.

 Is it really the case that neither NHC nor Hugs can implement a list
 of actions to be taken at the first convenient point after GC has
 finished without implementing the whole machinery of preemptive
 concurrency?  I take Malcolm Wallace's word for it that it isn't
 trivial, but why do you need for example asynchronous interruption
 of Haskell threads, wait queues, or time slices?  Surely what you
 need is some way of backing up the state upon return from GC in such
 a way that you can run the queued IO actions, which may be hard but
 is a long way off preemptive concurrency.

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.

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?

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

 If it's really impossible for NHC or Hugs to implement this, I think
 I would still rather it was left to the NHC and Hugs documentation
 to admit that exported Haskell functions basically don't work in
 some circumstances, rather than to the GHC documentation to say that
 actually they do.

It's a matter of taste how you do these things.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK

Re: Cheap ForeignPtr allocation

2002-09-04 Thread Alastair Reid


 Nevertheless, I think even without the tricks I'm using in GHC, the
 case where a ForeignPtr is used in conjunction with malloc()/free()
 is one which is likely to be optimisable in any system with its own
 memory management.

I wasn't meaning so much that only GHC could take advantage of it
(though I think that is true at present) but that someone might come
along next week with a technique which avoids the problem altogether.

 [...] 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?  If the latter, I imagine that a
custom allocator would have similar performance to using pinned
objects.  (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.

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



Proposed change to ForeignPtr

2002-09-03 Thread Alastair Reid


[Now that we've gotten the library specification issue out of the way,
I'd like to revive discussion of this topic.  Last time we discussed
it, there seemed to be concensus that we would make a change but I
didn't get much response when I made a concrete proposal.  I'd like to
resolve this promptly so that the impending Hugs release can match
what the spec says (or vice-versa...).]

Since requiring ForeignPtr.newForeignPtr would require preemptive
concurrency (see previous discussion), I propose the following changes:

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.


-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Cheap ForeignPtr allocation

2002-09-02 Thread Alastair Reid


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

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



Re: Updates to FFI spec

2002-08-13 Thread Alastair Reid


 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.

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



Re: Library archives

2002-08-12 Thread Alastair Reid


 Under .NET each DLL has its own namespace, so the [lib] spec is
 needed to disambiguate.  Since it's a namespace issue, I'd feel
 better if on .NET the name of the C function took a different form
 (perhaps lib.function) and [lib] is removed from the spec.

Isn't that just a different syntax for the same thing?

The thing I don't understand here is why .net issues affect the ccall
calling convention and not the dotnet calling convention?

I'm totally happy with defining dotnet to be ccall plus [lib] (or
lib.) specifications (much as stdcall is defined as a small delta on
ccall).  I know what that means and it is implementable on platforms
which support dotnet.  It is trying to make C fit into the .net scheme
of things which causes problems.

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

haskell-report/ffi

(and don't forget the grammar.sty file I pointed at in the commit message)

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



Re: Updates to FFI spec

2002-08-11 Thread Alastair Reid


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

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

Maybe SimonM and Malcolm do.  

I know GHC has an interface already and I suspect that NHC will too.
GHC and Hugs both call it performGC but this doesn't match the naming
convention used in the ffi and it is expensive to use with
generational GC (since there is no way to indicate that a partial GC
may be enough).

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

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

Malcolm and I both found it possible to interpret the spec as meaning
that the header files could be ignored.  If that isn't what the report
means, the wording should be strengthened.


[My concern with specifying header files in foreign imports is twofold:
1) It suggests the existence of multiple namespaces when I very much
   doubt that anyone would every implement that.
2) It is awfully repetitive because you have to mention the header files
   on every foreign import just in case anyone ever did implement
   multiple namespaces.  (Other side of the same problem.)
I'm not arguing for a change here - just saying that I wouldn't argue
against one.]


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

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

Hugs doesn't have anything resembling hs_init at the moment so I can't
say for sure.  I think it can be done as a thin layer on top of the
the existing spec though so I don't think it's that hard.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposed change to ForeignPtr

2002-08-09 Thread Alastair Reid


 I assume you meant
   makeForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)

Oops, yes.

 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.

 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.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Updates to FFI spec

2002-08-09 Thread Alastair Reid


For those not on the cvs mailing list:

I've applied all the changes discussed over the last 2 moniths that
received some support and no dissent.
  
  Changes since RC5:
  * Author list: changed Alastair Reid's institution
  * 4.1.1: Removed [lib] from impent syntax and discussion
  * 4.1.3: Added parentheses round FunPtr ft to make it easier to 
   understand a tolerably complex type.
  * 4.1.4: Removed all mention of library objects
  * 6: Specified that HsBool==int in table2
   Relabelled column 1 in table 3 (C symbol - CPP symbol)
   Replaced 0 and 1 with HS_BOOL_FALSE/TRUE

You will need this file:

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

to build it.  (I came close to adding this file to the repo but
figured that Manuel must have a reason for not having done so
himself.)

Changes not applied:

- I really, really want to resolve the ForeignPtr issues soon.

http://www.mail-archive.com/ffi@haskell.org/msg00655.html
http://www.mail-archive.com/ffi@haskell.org/msg00544.html
http://www.mail-archive.com/ffi@haskell.org/msg00545.html

- I'd like to see a standard way to call the GC from C

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

- I see the question of Function prototypes as a portability problem
  waiting to happen.  Either Hugs and GHC are right (you should use the
  user-supplied header file or NHC is right (you should ignore the
  header file).  They can't both be right if we want portable code
  so the report should be clear about which one is right.

  (Given my druthers, I'd drop header files from the foreign import syntax
  and say that you have to specify it on the command line or propose that
  we standardize some variant of the GHCism {-# -include foo.h #-}.  But
  I'm not excited enough about it to push hard for this.)

- Changes to hs_init 

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


--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposed change to ForeignPtr

2002-08-09 Thread Alastair Reid


Alastair wrote [snip]
 makeForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO ForeignObj

 [snip] I don't understand this proposal.  What is a ForeignObj?

Sorry, that was a typo.  The result type should be 

  IO (ForeignPtr a)

 I call a C function, which gives me a cString :: Ptr CChar, and it's
 my responsibility to free it when I've finished with it.  So I
 convert it to a ForeignPtr:

foreignPtr - mkForeignPtr cString

 and then always refer to the pointer via foreignPtr.  When
 foreignPtr is garbage collected the space is freed.  So how do I do
 this with your proposal?

With the existing spec, you would write:

 foreign import free :: Ptr CChar - IO ()

 foo = do
   ...
   foreignPtr - newForeignPtr cString (free cString)
   ...

With my proposal, you would write:

 foreign import  free :: FunPtr (Ptr CChar - IO ())

 foo = do
   ...
   foreignPtr - newForeignPtr cString free
   ...

All the rest of your code to manipulate ForeignPtrs remains the same.
(Well, there's a corresponding change in addForeignFinalizer if you
happen to use that.)


-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

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



Re: Generating Function Prototypes

2002-07-07 Thread Alastair Reid


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

I think this is a very misleading way to describe the problem.  A
major goal of the ffi is to provide a portable way of interfacing
Haskell to C.  If we regard the header file as an optional extra which
some compilers need and some don't, then we have failed in that goal.
The effort of producing a header file is sufficient that ffi code
supplied without them will be very hard to port to ghc -fvia-C (and,
as I understand it, -fvia-C is considered the more stable platform
especially when doing ffi work).

One might argue that the whole area of ffi is rife with portability
problems because the portability problems encountered when writing,
compiling and linking C code leak into the ffi.  That is true to some
degree but:

1) We have tools like autoconf which help make the C side of things
   more tractable.

2) The task of transferring a few linker flags from one makefile to
   another is quite small compared with the task of writing a 
   suitable header file.

3) If I have m Haskell compilers and n platforms, then I have m*n
   combinations to worry about if the ffi is not portable but only n
   combinations to worry about if the ffi is portable between
   compilers.

-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/

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



Re: Generating Function Prototypes

2002-07-04 Thread Alastair Reid


 Errm, shouldn't that be: [...]
 Or is there some other trick involved here?

Sorry, yes it should - just me getting confused in translating between
Haskell's

  f :: A - B

and C's

  B f(A);

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



  1   2   >