advancePtr for ForeignPtr

2009-02-19 Thread Henning Thielemann
I want to have an advancePtr on ForeignPtr in order create a subarray. Is this reasonable and possible? Do I have to use 'touchForeignPtr' as finalizer of the subarray's ForeignPtr in order to assert that the superarray lives at least as long as the subarray? Anyway I'd prefer a function

RE: How to force finalization of ForeignPtr

2003-12-22 Thread Simon Marlow
(finalizeForeignPtr) where import GHC.ForeignPtr import Data.IORef finalizeForeignPtr :: ForeignPtr a - IO () finalizeForeignPtr foreignPtr = do finalizers - readIORef refFinalizers sequence_ finalizers writeIORef refFinalizers [] where refFinalizers = case

Re: new ForeignPtr without finalizers

2003-07-07 Thread Sven Panne
Manuel M T Chakravarty wrote: [ newForeignPtr / addForeignPtrFinalizer argument order ] This is the last outstanding issue. Shall we swap? I am torn. The swapped argument order seems more appropriate, but it will break code. Shall we have one more breakage before it's all frozen? I think that

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

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

Re: new ForeignPtr without finalizers

2003-06-12 Thread Manuel M T Chakravarty
. Actually, I think I prefer Ashley's idea of separating the creation of a ForeignPtr from the addition of a FinalizerPtr. So how about: newForeignPtr :: Ptr a - IO (ForeignPtr a) addForeignPtrFinalizer :: FinalizerPtr a - ForeignPtr a - IO () newForeignPtrWithFinalizer

Re: new ForeignPtr without finalizers

2003-06-11 Thread Manuel M T Chakravarty
consider: newForeignPtr :: [FinalizerPtr a] - Ptr a - IO (ForeignPtr a) addForeignPtrFinalizers :: [FinalizerPtr a] - ForeignPtr a - IO () True, but it would also break old code and I doubt that users would often add more than one finaliser at a time. Cheers, Manuel

Re: new ForeignPtr without finalizers

2003-06-11 Thread Manuel M T Chakravarty
is that newForeignPtr_ :: Ptr a - IO (ForeignPtr a) and with *reversed* arguments also newForeignPtr myFinalizer :: Ptr a - IO (ForeignPtr a) In other words, it seem much more likely that one would partially apply `newForeignPtr' to a finaliser than to a pointer that is to be finalised. But this is a minor

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

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

Re: new ForeignPtr without finalizers

2003-06-09 Thread Ashley Yakeley
be tempted to call newForeignPtr_). Specifically I want a ForeignPtr of a null Ptr that has no finalizers. I want a value of type ForeignPtr such that withForeignPtr will extract a null Ptr. My basic JNI ref type is newtype of a ForeignPtr. JNI gives me global references as Ptrs, and I wrap them

Re: new ForeignPtr without finalizers

2003-06-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED], Malcolm Wallace [EMAIL PROTECTED] wrote: Why would you want to? A ForeignPtr without any finalizers is semantically just a Ptr, plain and simple. I need a pointer type for which some values have finalizers, and some don't. -- Ashley Yakeley, Seattle WA

Re: new ForeignPtr without finalizers

2003-06-09 Thread Axel Simon
On Mon, Jun 09, 2003 at 01:21:38PM +0100, Malcolm Wallace wrote: Ashley Yakeley [EMAIL PROTECTED] writes: Specifically I want a ForeignPtr of a null Ptr that has no finalizers. Ah, this makes sense. I wonder if we should add the following to the FFI spec module ForeignPtr

Re: new ForeignPtr without finalizers

2003-06-09 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote, Ashley: How do I create a new ForeignPtr that doesn't have any finalizers? Malcolm: Why would you want to? addForeignPtrFinalizer lets you add them later. I'm guessing that Ashley is making heavy use of this ability. [What we have

Re: new ForeignPtr without finalizers

2003-06-09 Thread Alastair Reid
`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

Re: new ForeignPtr without finalizers

2003-06-09 Thread Dean Herington
a - IO (ForeignPtr a) addForeignPtrFinalizers :: [FinalizerPtr a] - ForeignPtr a - IO () -- Dean ___ FFI mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/ffi

Re: new ForeignPtr without finalizers

2003-06-09 Thread Ashley Yakeley
be this: newForeignPtr :: Ptr a - IO (ForeignPtr a) addForeignPointerFinalizer :: ForeignPtr a - FinalizerPtr a - IO () That gives you an empty finalizers function and an add finalizers function, like [] and (:). I don't really care, actually, as long as I can obtain the same functionality. -- Ashley

Re: ForeignPtr naming

2003-03-26 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote, As Haskell finalizers need pre-emptive concurrency, maybe they should go somewhere related to concurrency. Or we could have a Foreign.Concurrent. Ok, how about Foreign.Concurrent.newForeignPtr and Foreign.Concurrent.addForeignPtrFinalizer? i.e.

RE: ForeignPtr naming

2003-03-20 Thread Simon Marlow
taken by 'oldNewForeignPtr'. That implies the functionality is deprecated, rather than just non-portable, which is not the case at all. I'm assuming that we want to keep these functions in some form in GHC - where to put them is one issue; Foreign.ForeignPtr is a possibility (but not ForeignPtr

RE: ForeignPtr query

2002-12-04 Thread Simon Marlow
(int *) on all platforms i need to run this on (yuk). - plead for a general stick this arbitrary (small) C object in an optimiser-impervious box generalisation of ForeignPtr. There was a proposal for such a thing kicking around recently, and I think there's no real problems with it. Although

ForeignPtr query

2002-12-02 Thread Peter Gammie
-impervious box generalisation of ForeignPtr. 2. how do i import a function pointer under ghc5.02? in 5.04 i say: foreign import ccall bdd_reorder_stable_window3 bdd_reorder_stable_window3 :: FunPtr (BDDManager - IO ()) and that works (i.e. i can treat it like any other Haskell function). 3

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

2002-11-19 Thread Simon Marlow
The current `modifyMVar`, though exception safe, is not atomic in the same way that the proposed `atomicModifyMVar` would be. Unless I misunderstand, during the execution of `modifyMVar`'s second argument, the mvar is empty and could be filled by some other thread. With

RE: ForeignPtr-related signatures

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

Re: ForeignPtr-related signatures

2002-11-18 Thread Sven Panne
Malcolm Wallace wrote: [...] there was considerable sympathy for using new names for the C-finaliser-only functions, preferably incorporating the word unsafe [...] I'd really prefer that, too. Simon Marlow wrote: GHC 5.04.2 won't adopt any library changes, as it's only a patchlevel release

RE: ForeignPtr-related signatures

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

Re: ForeignPtr-related signatures

2002-11-18 Thread Ross Paterson
the people who need them have given up. But I certainly hope that the execution order of finalizers on a single ForeignPtr is specified, and I think I saw SimonM agreeing to it. At the minimum it is necessary to specify that any finalizer added to a ForeignPtr created with mallocForeignPtr runs

RE: ForeignPtr-related signatures

2002-11-18 Thread Simon Marlow
Simon Marlow wrote: [...] There was this, from Dean Herrington: http://haskell.cs.yale.edu/pipermail/ffi/2002-October/000940.html I don't have any strong feelings (I rarely do, where names are concerned). I would be happy with his proposal. We can leave the IORef stuff in

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

2002-11-18 Thread Dean Herington
Simon Marlow wrote: Simon Marlow wrote: [...] There was this, from Dean Herrington: http://haskell.cs.yale.edu/pipermail/ffi/2002-October/000940.html I don't have any strong feelings (I rarely do, where names are concerned). I would be happy with his proposal. We can

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

2002-11-18 Thread Dean Herington
I wrote: One might reasonably worry about the proliferation of MVar manipulation functions. I think it's useful to realize that there are semantically only four primitives in the proposed extended interface: `newEmptyMVar`, `atomicModifyMVar`, `atomicTryModifyMVar`, and `addMVarFinalizer`.

ForeignPtr-related signatures

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

Re: ForeignPtr

2002-11-08 Thread Ross Paterson
On Fri, Nov 08, 2002 at 10:32:20AM -, Simon Marlow wrote: Ross's proposal provides a subtly different mechanism. It's not mine -- Ashley Yakeley proposed it in http://www.haskell.org/pipermail/glasgow-haskell-users/2001-September/002289.html ___

ForeignPtr

2002-11-07 Thread Ross Paterson
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. In Sept 2001 Ashley Yakeley asked why ForeignPtr couldn't be generalized, i.e

Re: ForeignPtr

2002-11-07 Thread Alastair Reid
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

Re: ForeignPtr

2002-11-07 Thread Ross Paterson
On Thu, Nov 07, 2002 at 04:00:48PM +, Alastair Reid wrote: 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)? ___ 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

Re: ForeignPtr

2002-11-07 Thread Ross Paterson
On Thu, Nov 07, 2002 at 04:53:04PM +, Alastair Reid wrote: 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

RE: ForeignPtr

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

RE: ForeignPtr

2002-11-07 Thread Simon Marlow
That was Ashley's original proposal, but SimonM responded in http://www.haskell.org/pipermail/glasgow-haskell-users/2001-September/00 2290.html http://www.haskell.org/pipermail/glasgow-haskell-users/2001-September/00 2304.html I think I had the wrong end of the stick; or at least I hadn't

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

Re: ForeignPtr

2002-11-07 Thread John Meacham
. 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

Re: Proposed change to ForeignPtr

2002-09-11 Thread George Russell
Alastair Reid wrote: [snip] 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. Am I really asking that much? In that paper you wrote

RE: Proposed change to ForeignPtr

2002-09-11 Thread Simon Peyton-Jones
I confess that I have not followed the twists and turns of this discussion, but it seems to have gotten more complicated than necessary. There are several separate issues. 1. Can a finaliser for a Haskell value be an arbitrary Haskell computation? For GHC, yes. For Hugs, no (and for good

RE: Proposed change to ForeignPtr

2002-09-11 Thread Simon Marlow
I'm afraid George's questions have also rekindled my curiosity about whether implementing Haskell finalizers is really as hard as it sounds. Much has been written, but I still don't think we've got to the nub of the issue. On the face of it, if you can implement 'foreign import ccall safe', then

Re: Proposed change to ForeignPtr

2002-09-11 Thread George Russell
Manuel M T Chakravarty wrote: [snip] 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. [snip] Yeah yeah I know,

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

Re: Cheap ForeignPtr allocation

2002-09-11 Thread Manuel M T Chakravarty
I agree with SimonM that the proposed routines have useful applications. Furthermore, it is trivial for Haskell systems to implement these routines. Hence, I will include them into the spec unless there are serious objections. Cheers, Manuel ___ FFI

Re: Proposed change to ForeignPtr

2002-09-10 Thread Manuel M T Chakravarty
Manuel M T Chakravarty [EMAIL PROTECTED] wrote, We seem to have a consensus on this one. We change the type of the existing functions to newForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a) addForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO

Re: Proposed change to ForeignPtr

2002-09-10 Thread George Russell
Manuel wrote (snipped) I have changed this in the spec now. I attach the wording used in the spec. \item[newForeignPtr ::\ Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a)] Turn a plain memory reference into a foreign object by associating a finalizer with the reference

Re: Proposed change to ForeignPtr

2002-09-10 Thread Alastair Reid
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

Re: Proposed change to ForeignPtr

2002-09-10 Thread George Russell
is the conflict? [snip] Does at a later moment in time mean that it is late enough that we can be sure calling Haskell will be OK? Look, suppose for simplicity that Foogle implements an identical FFI to Haskell. So we have (Haskell ForeignPtr A) == (Foogle StablePtr A) (Foogle StablePtr A) points

Re: Proposed change to ForeignPtr

2002-09-10 Thread George Russell
Alastair Reid wrote [snip] We should provide a C function hs_freeStablePtr and explicitly say that it is safe to call this from inside a finalizer. [snip] This would be the simplest solution, but would not permit you to do anything more sophisticated at the Haskell side, such as reference

Re: Proposed change to ForeignPtr

2002-09-10 Thread George Russell
Malcolm Wallace wrote [snip] Quite simply, no finaliser (whether in Foogle or Haskell) should be capable of triggering a garbage collection within its call. This condition is absolutely necessary to prevent a cascade effect of cross-language garbage collections, where a finaliser in Haskell

Re: Proposed change to ForeignPtr

2002-09-10 Thread Malcolm Wallace
to delay any Haskell calls consequent on finaliser 1 until [leave GC], don't you? How can it? Because the Haskell calls don't happen until the Foogle GC invokes them. Ok, you have a Haskell ForeignPtr which is really a Foogle object. It becomes garbage. At the next Haskell GC, its finaliser is run

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

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

RE: Cheap ForeignPtr allocation

2002-09-04 Thread Simon Marlow
[...] using a ForeignPtr here, with free() as its finalizer, adds so much overhead that [...] Where is the overhead coming from? Is it the cost of a C call or the cost of the standard malloc library? It's the combined cost of - malloc() - creating a weak pointer to register

RE: Proposed change to ForeignPtr

2002-09-04 Thread Simon Marlow
1) Add these functions: makeForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a) attachForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO () It is implementation defined whether the free functions are allowed to call

Re: Cheap ForeignPtr allocation

2002-09-03 Thread Manuel M T Chakravarty
Simon Marlow [EMAIL PROTECTED] wrote, I'd like to propose two new functions for the ForeignPtr interface: mallocForeignPtr :: Storable a = IO (ForeignPtr a) mallocForeignPtrBytes :: Int - IO (ForeignPtr a) (the names can change, of course). The implementations

RE: Cheap ForeignPtr allocation

2002-09-03 Thread Simon Marlow
ByteArray# and let the GC free it. (it needs to be pinned so that it can be passed to foreign functions which might re-enter the RTS and trigger GC, etc.) This proposed extension to ForeignPtr is just taking the idea one step further: we can use the same trick for ForeignPtrs too, at least in the common

Proposed change to ForeignPtr

2002-09-03 Thread Alastair Reid
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

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: Cheap ForeignPtr allocation

2002-09-02 Thread Simon Marlow
Can you achieve the same performance gain by adding some rewrite rules? Perhaps you could try to spot (=) malloc (\p - newForeignPtr p free) Hmmm. Actually I'd like to do both: add the functions, because they encapsulate a common case and guarantee a speed improvement if you use

Re: Proposed change to ForeignPtr

2002-08-12 Thread Malcolm Wallace
Alastair Reid [EMAIL PROTECTED] writes: I'm not sure which position you're preferring here. I lean a bit towards using the old names for the new functions (the ones with free functions) and finding new names for the old functions (the ones with closure arguments). That would be my

RE: Proposed change to ForeignPtr

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

Re: Proposed change to ForeignPtr

2002-08-12 Thread Manuel M T Chakravarty
We seem to have a consensus on this one. We change the type of the existing functions to newForeignPtr :: Ptr a - FunPtr (Ptr a - IO ()) - IO (ForeignPtr a) addForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a - IO ()) - IO () For GHC, I propose to put the closure-based versions

Re: Proposed change to ForeignPtr

2002-08-10 Thread Manuel M T Chakravarty
Alastair Reid [EMAIL PROTECTED] wrote, What do you expect to happen if the finaliser calls a foreign exported function? Good question. I do not expect that to work on any platform that has difficulty implementing newForeignPtr (because you could use it to implement newForeignPtr).

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

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

ForeignObj and ForeignPtr

2001-05-01 Thread Sven Panne
In the course of trying to find out GHC's status quo of typing foreign declarations and scribbling together the forthcoming typing rules, I stumbled over ForeignObj/ForeignPtr. There was a lively discussion about this some time ago IIRC, but I'm unsure about a few things: * ForeignObj has

Proposal #1: ForeignPtr

2000-12-01 Thread Simon Marlow
Dear FFI folks, I'd like to summarise the current proposals on the table and see if we can get a consensus. Proposal #1: replace ForeignObj with (ForeignPtr a). * new module ForeignPtr, with the following interface: module ForeignPtr ( ForeignPtr