Re: Running a final finaliser

2004-01-06 Thread Adrian Hey
On Monday 05 Jan 2004 3:14 pm, Simon Marlow wrote:
  The other complication I can see is that ForeignPtr finalisers can't
  be Haskell. So I have to call the Haskell finalisation from C.
  Is that safe? I'm afraid I still don't fully understand why Haskell
  finalisers are unsafe or why (if) calling Haskell from a C finaliser
  (which then called C land again) would be any safer.

 If you don't mind your code being non-portable, then Foreign.Concurrent
 provides Haskell finalisers.

Oh yes, so it does :-) I'd just been looking at the FFI documentation
(only). Thanks for pointing that out.

 This support will be available only on
 Haskell implementations which implement pre-emptive concurrency (i.e.
 just GHC for now).

OK, I think understand now thanks to Alistair Reids explanation. I had
been trying to keep my code portable (it's a library binding I hope
to make available to Haskell folk sometime soon). But this seems
to be quite difficult. AFAICS the situation is that the only really
portable solution to this problem is for the reference counting thing
(or doubly linked lists or whatever) to be done in C (which I guess is
what everybody's been saying all along :-).

Regards
--
Adrian Hey  


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


Re: Running a final finaliser

2004-01-06 Thread Adrian Hey
Hello,

Thanks for that explanation, I see the problem now.

Though to be honest, I'm not convinced that the situation
for Haskell implementations which don't implement pre-emptive
concurrency need be as bad as you suggest. But that's probably
presumptious of me seeing as I know little about the
implementations of either Hugs or nhc (or ghc for that matter:-)

I can see there is a potential problem with single threaded programs
which may never call yield, though even in this situation it I would
think it would be relatively straight forward to have an implicit
yield to finalisers at appropriate points (no partially reduced
thunks in the heap).

But then again, I guess the logic is that since foreign object
finalisers will usually be foreign functions which don't re-enter
Haskell it's probably not worth the effort.

The other thing that strikes me about this is don't we also have
the same potential problem with weak pointer finalisers? Can they
be supported in Haskell without pre-emptive concurrency?

Regards
--
Adrian Hey 

On Monday 05 Jan 2004 4:39 pm, Alastair Reid wrote:
   I'm afraid I still don't fully understand why Haskell
   finalisers are unsafe or why (if) calling Haskell from a C finaliser
   (which then called C land again) would be any safer.

 The FFI standard doesn't say that calling C finalizers is unsafe (which
 would imply that the finalizers potentially do something naughty).  Rather,
 the standard says that finalizers are called in a restricted context in
 which they are not allowed to call back into Haskell.

 The reason that finalizers must be written in C and cannot call into
 Haskell is that it requires pretty much all the machinery needed to
 implement preemptive concurrency (multiple C stacks, context switches,
 etc.) which was felt to be an excessively high burden on a Haskell
 implementation just to let you call C functions.  (Of course, GHC already
 has this machinery which is why they provide enhanced functionality.)

 Why does it require most of the machinery of preemptive concurrency?
 Suppose that a finalizer requires the value of something that is currently
 being evaluated by the main thread.  (This is very common and pretty much
 impossible to reason about in Haskell.  For example, it could be a
 dictionary object or the thunk '(==) dict_Int'.)  The correct thing to do
 if this happens is to block the finalizer, run the main thread until the
 shared thunk is updated with a value, and then restart the finalizer.  To
 block a thread in this way, we have to switch C stacks, perform a context
 switch, etc.  QED.

 --
 Alastair Reidhaskell-consulting.com


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


RE: Running a final finaliser

2004-01-05 Thread Simon Marlow
 The other complication I can see is that ForeignPtr finalisers can't
 be Haskell. So I have to call the Haskell finalisation from C.
 Is that safe? I'm afraid I still don't fully understand why Haskell
 finalisers are unsafe or why (if) calling Haskell from a C finaliser
 (which then called C land again) would be any safer. 

If you don't mind your code being non-portable, then Foreign.Concurrent
provides Haskell finalisers.  This support will be available only on
Haskell implementations which implement pre-emptive concurrency (i.e.
just GHC for now).

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


Re: Running a final finaliser

2004-01-05 Thread Alastair Reid

  I'm afraid I still don't fully understand why Haskell
  finalisers are unsafe or why (if) calling Haskell from a C finaliser
  (which then called C land again) would be any safer.

The FFI standard doesn't say that calling C finalizers is unsafe (which would 
imply that the finalizers potentially do something naughty).  Rather, the 
standard says that finalizers are called in a restricted context in which 
they are not allowed to call back into Haskell.

The reason that finalizers must be written in C and cannot call into Haskell 
is that it requires pretty much all the machinery needed to implement 
preemptive concurrency (multiple C stacks, context switches, etc.) which was 
felt to be an excessively high burden on a Haskell implementation just to let 
you call C functions.  (Of course, GHC already has this machinery which is 
why they provide enhanced functionality.)

Why does it require most of the machinery of preemptive concurrency? Suppose 
that a finalizer requires the value of something that is currently being 
evaluated by the main thread.  (This is very common and pretty much 
impossible to reason about in Haskell.  For example, it could be a dictionary 
object or the thunk '(==) dict_Int'.)  The correct thing to do if this 
happens is to block the finalizer, run the main thread until the shared thunk 
is updated with a value, and then restart the finalizer.  To block a thread 
in this way, we have to switch C stacks, perform a context switch, etc.  QED.

--
Alastair Reidhaskell-consulting.com

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


Re: Running a final finaliser

2004-01-01 Thread Adrian Hey
On Wednesday 31 Dec 2003 10:05 am, Adrian Hey wrote:
 On Wednesday 31 Dec 2003 8:56 am, Adrian Hey wrote:
  Intended use is something like this...
 
  {-# notInline libXYZRef #-}
  libXYZRef :: LibRef
  libXYZRef = unsafePerformIO newLibRef
 
  main :: IO ()
  main = finally (initLibXYZ  userMain) (killLibRef libXYZRef
   shutDownLibXYZ)
  -- initLibXYZ and shutDownLibXYZ are Haskell bindings to functions
  supplied -- by libXYZ

 Actually, using..
  main = finally (initLibXYZ  userMain)
 (performGC  killLibRef libXYZRef shutDownLibXYZ)

 seems to fix the problem, which isn't too surprising I guess.
 But then again, if this is a reliable solution there's no need
 for LibRef after all :-)

Hmm, further experiments with creating zillions of garbage
ForeignPtrs (not just 1) reveals that the problem only occurs
if *no* garbage collection has occured before the program shuts
down. In other words, as long as at least one garbage collection
has occured, it doesn't matter if library shutdown occurs immediately
in response to killLibRef or if it's deferred until the reference
count hits zero as a result of finalisers being called. (This test
is without the explicit performGC of course.)

So (hoping I will not have to eat my words:-) I'm begining to suspect
this is a buglet in the ghc rts somewhere.

Regards
--
Adrian Hey





   


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


Re: Running a final finaliser

2003-12-31 Thread Adrian Hey
Hello again,

I've tried the simplest possible reference counting approach which should
be OK if all finalisers are run eventually (as I think is the case currently
with ghc 6.2).

But I don't seem to be able to get it to work. I've attached the library
reference counting code (LibRef module) to the end of this message.

Intended use is something like this...

{-# notInline libXYZRef #-}
libXYZRef :: LibRef
libXYZRef = unsafePerformIO newLibRef

main :: IO ()
main = finally (initLibXYZ  userMain) (killLibRef libXYZRef shutDownLibXYZ)
-- initLibXYZ and shutDownLibXYZ are Haskell bindings to functions supplied
-- by libXYZ

userMain :: IO ()
-- userMain creates ForeignPtrs to library objects using addLibRef  

I'm testing by creating 1 ForeignPtr reference using addLibRef and
dropping it immediately thereafter (so it's garbage, but not detected
as such immediately). Running with the -B rts option tells me when
garbage collection has occured.

The problem is I get a fail: loop error if no garbage collection
has occured when killLibRef is called (I.E. killLibRef saves shutDownLibXYZ
for later use because the reference count is non-zero).

But everything works fine if I wait for garbage collection to occur before
calling killLibRef.  

Does anybody have any idea what might be going wrong here?

Personally I'm a bit suspicious of the use of the cToH and hToC functions
in addLibRef, but I'm not aware of any alternative if you want to mix in
some Haskell code with a finaliser.

Thanks for any advice. LibRef code follows below..

module LibRef
(LibRef  -- data LibRef
,newLibRef   -- IO LibRef
,addLibRef   -- LibRef - FinalizerPtr a - Ptr a - IO (ForeignPtr a)
,killLibRef  -- LibRef - IO () - IO ()
) where

import Data.IORef
import Foreign.Ptr
import Foreign.ForeignPtr
import Control.Concurrent.MVar

foreign import ccall dynamic cToH :: FinalizerPtr a - (Ptr a - IO ())
foreign import ccall wrapper hToC :: (Ptr a - IO ()) - IO (FinalizerPtr a)

newtype LibRef = LibRef (MVar Int-- Reference count (and lock)
,IORef (IO ())   -- Shutdown action
)

-- Create a new LibRef
newLibRef :: IO LibRef
newLibRef = do
  countRef  - newMVar 0 -- No references
  killitRef - newIORef $ return ()  -- No shutdown action initially
  return $ LibRef (countRef,killitRef) 

-- Similar to newForeignPtr. Creates a ForeignPtr reference to a library
-- object and increments the LibRef reference count. The actual finaliser
-- used runs the suppied finaliser (second arg) and then decrements the
-- LibRef reference count.
addLibRef :: LibRef - FinalizerPtr a - Ptr a - IO (ForeignPtr a)
addLibRef libRef@(LibRef (countMVar,_)) finalise ptr = do
  finalise' - hToC $ \p - do cToH finalise p
   decLibRef libRef
  count - takeMVar countMVar   -- Read (and lock)
  putMVar countMVar $! (count+1)-- Increment (and unlock)
  newForeignPtr finalise' ptr

-- Decrement a LibRef reference count. If the resulting reference
-- count is zero whatever action is stored in killitRef is executed
-- (and killitRef is reset to return ()) 
decLibRef :: LibRef - IO ()
decLibRef (LibRef (countMVar,killitRef)) = do
  putStrLn decLibRef
  count - takeMVar countMVar-- Read and lock
  case count of
0 - error decLibRef applied to zero reference count
1 - do killit - readIORef killitRef-- Get configured kill
writeIORef killitRef $ return () -- Reset killitRef 
putMVar countMVar 0  -- Reset and unlock
killit   -- Kill it
putStrLn No Refs
_ - putMVar countMVar $! (count-1)  -- Decrement and unlock

-- Call this when the library is no longer needed.
-- Second Arg is library shutdown action. This is performed immediately
-- if reference count == 0. Otherwise it is stored and executed by the
-- last finaliser (when reference count hits 0). 
killLibRef :: LibRef - IO () - IO ()
killLibRef (LibRef (countMVar,killitRef)) killit = do
  count - takeMVar countMVar-- Read and lock
  if count == 0 then do writeIORef killitRef $ return () -- Reset killitRef
putMVar countMVar count  -- Unlock
killit   -- Execute now
putStrLn Killed now
else do writeIORef killitRef killit  -- Save for later
putMVar countMVar count  -- Unlock
putStrLn Killed later

Regards
--
Adrian Hey

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


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
On Monday 22 Dec 2003 10:13 am, Simon Marlow wrote:
  Thanks for your reply. I'm afraid it's left me even
  more confused about which way to go with this :-(
 
  If it's possible that future Haskell FFI's don't guarantee
  that all finalisers are run then this more or less rules
  out the use of the reference counting solution (which
  wasn't particularly attractive anyway because it needs to
  be done in C AFAICS :-). If users who want this behaviour
  are required to code it themselves, it seems to require that
  they maintain a global list of all allocated ForeignPtrs.
  But doing that naively will stop them being garbage collected
  at all, unless it's possible to do something clever using weak
  pointers. Perhaps it is possible (or maybe some tricks at the
  C level could be used) but I think it's a significant extra
  burden for FFI users.

 Yes, it would have to be a global list of weak pointers to ForeignPtrs.
 This topic has come up before, though not on this list.  See this
 message, and the rest of the thread:

 http://www.haskell.org/pipermail/cvs-ghc/2003-January/016651.html

 the thread also moved on to [EMAIL PROTECTED]:

 http://www.haskell.org/pipermail/ffi/2003-January/001041.html

 and be sure to check out the paper by Hans Boehm referenced in that
 message, it's a good summary of the issues involved.

Thanks, I'll take a look at the Boehm paper. I didn't keep up with
this discussion at the time, but now I see the relevance. 

Assuming the weak pointers solution is the way to go, I've been
re-aquainting myself with System.Mem.Weak and now I'm now wondering
what is an appropriate key for each ForeignPtr.

Would it be OK to use the ForeignPtr itself as it's own key?
(Seems OK to me, but this is a bit different from the memoisation
example so I thought I'd check.)

If so, then I guess the thing to do is to maintain a mutable doubly
linked list of Weak pointers to ForeignPtrs using IORef's and have
the finaliser for each weak pointer short out the corresponding
list cell. When the program terminates execute the finalisers
of all ForeignPtrs which remain in this list.

Hmm, this is getting awfully complicated, and I still have my
doubts about it for a couple of reasons..

1- Executing ForeignPtr finalisers directly (as in Krasimirs
   example) seems to be ghc specific.
2- If there is no guarantee whether or when ForeignPtr finalisers
   are run then it seems that it is possible that a Weak pointer
   finaliser has been run (thereby deleting the weak pointer
   reference from the list), but the corresponding ForeignPtr
   finaliser has *not* been run.

The solution to problem 2 would seem to be to not associate
any finaliser with with the ForeignPtr, but do all finalisation
in the Weak pointer finaliser. I guess that would cure problem
1 too.

What do folk think about this?   

 performGC doesn't do anything that you can rely on :-)

Oh, that's handy :-)

  Also, I could you explain what you mean by a suitable
  exception handler? I don't really understand this at all.
  I'd expected I may well end up using bracket or similar,
  but I'm not sure how exception handling is relevant to
  this problem.

 Start your program something like this:

   import Control.Exception (finally)

   main = my_main `finally` clean_up
   my_main = ... put your program here ...
   clean_up = ... all the cleanup code goes here ...

 You can additionally use finalizers to perform incremental cleanup
 during program execution, but the right way to clean up at the end is to
 use an exception handler as above.

Ah OK, I was hoping the whole thing would be something as simple
as this..

withLibXYX :: IO () - IO ()
withLibXYZ doit = finally (initialiseLibXYZ  doit)
  (performGC  shutdownLibXYZ)

Where initialiseLibXYZ and shutdownLibXYZ are simple foreign functions
imported from libXYZ. I think it's a real shame performGC or some other
similar function can't simply guarantee that all (garbage) ForeignPtr
finalisers have been run before calling shutdownLibXYZ :-(

Regards
--
Adrian Hey




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


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
On Monday 22 Dec 2003 8:53 pm, Carl Witty wrote:
Thanks for your reply. I'm afraid it's left me even
  
   more confused about which way to go with this :-(

 Is your problem something you could handle with a C atexit() handler?

That's a good idea. With ghc I guess this will work, assuming..
1- ghc rts runs all ForeignPtr finalisers before it shutsdown.
2- ghc rts is shutdown before atexit handlers are executed. 

I both think 1  2 are true with ghc at present, but Simon M.
indicated that 1 might not be true in future for ghc (or other
Haskell implementations). That said, the current FFI spec
states at bottom of p.14..

There is no guarantee on how soon the finalizer is executed
after the last reference to the associated foreign pointer
was dropped; this depends on the details of the Haskell storeage
manager. The only guarantee is that the finalizer runs before
the program terminates.

So I'm still confused :-)

Actually, though I think it would work for me, it's probably
not as general as some folk might want (they might want to
shutdown the library and free up whatever resources it claimed
earlier in program execution, not just at exit).

Regards
--
Adrian Hey


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


RE: Running a final finaliser

2003-12-23 Thread Simon Marlow
 Assuming the weak pointers solution is the way to go, I've been
 re-aquainting myself with System.Mem.Weak and now I'm now wondering
 what is an appropriate key for each ForeignPtr.

Before we go down that route, I want to be sure that it's actually
necessary to use weak pointers.  It sounds like your application has the
following properties:

  - there is a library that can allocate some resources, where
each resource is represented by a ForeignPtr

  - a resource needs to be released when it is no longer referenced

  - at some point, we would like to free *all* outstanding resources
(either at the end of the program, or when the library is no
longer required).

If this is the case, I'd do it something like this:

  - keep a global list of the pointers still to be released, probably
a doubly-linked list.  Lock the whole thing with an MVar.  Elements
are Ptrs, not ForeignPtrs.

  - the finaliser on each ForeignPtr removes the corresponding Ptr from
the list.

  - the final cleanup routine explicitly releases all the remaining
Ptrs in the list, holding the MVar lock as it does so to avoid
race conditions with finalisers.

Weak pointers aren't required, AFAICT.

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


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
Hello

On Tuesday 23 Dec 2003 9:27 am, Simon Marlow wrote:
  Assuming the weak pointers solution is the way to go, I've been
  re-aquainting myself with System.Mem.Weak and now I'm now wondering
  what is an appropriate key for each ForeignPtr.

 Before we go down that route, I want to be sure that it's actually
 necessary to use weak pointers.  It sounds like your application has the
 following properties:

   - there is a library that can allocate some resources, where
 each resource is represented by a ForeignPtr

Basically, but there are also some hardware resources (other than memory)
which are claimed just as a result of library initialisation (before any
library objects have been created).

   - a resource needs to be released when it is no longer referenced

Yes, that's right.

   - at some point, we would like to free *all* outstanding resources
 (either at the end of the program, or when the library is no
 longer required).

I want to free all heap space used by library objects, then free whatever
other hardware resources have been claimed by the library (by calling
the appropriate shutdown routine).

 If this is the case, I'd do it something like this:

   - keep a global list of the pointers still to be released, probably
 a doubly-linked list.  Lock the whole thing with an MVar.  Elements
 are Ptrs, not ForeignPtrs.

   - the finaliser on each ForeignPtr removes the corresponding Ptr from
 the list.

   - the final cleanup routine explicitly releases all the remaining
 Ptrs in the list, holding the MVar lock as it does so to avoid
 race conditions with finalisers.

 Weak pointers aren't required, AFAICT.

Maybe, I'd forgotten that I could get at the Ptr inside each ForeignPtr.
I guess I've still got to think about the consequences of ForeignPtr
finalisers being run after the final shutdown. (Making each
List cell an IORef (Maybe something) would do that I think).

The other complication I can see is that ForeignPtr finalisers can't
be Haskell. So I have to call the Haskell finalisation from C.
Is that safe? I'm afraid I still don't fully understand why Haskell
finalisers are unsafe or why (if) calling Haskell from a C finaliser
(which then called C land again) would be any safer. 

Thanks for the idea though. I'll play about with a few implementations
of these ideas after christmas and see what problems I encounter.

Regards
--
Adrian Hey

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


Re: Running a final finaliser

2003-12-22 Thread Tomasz Zielonka
On Mon, Dec 22, 2003 at 10:13:42AM -, Simon Marlow wrote:
  
 performGC doesn't do anything that you can rely on :-)  In practice, it
 probably starts all the finalizers that are ready to run, but it
 certainly doesn't wait for their termination.

Moreover, it is not guaranteed that performGC will trigger a full GC.
Most often it will reclaim only the 0th generation. I think it would be
useful to have something like performFullGC.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Running a final finaliser

2003-12-22 Thread Tomasz Zielonka
On Mon, Dec 22, 2003 at 11:34:14AM +0100, Tomasz Zielonka wrote:
 
 Moreover, it is not guaranteed that performGC will trigger a full GC.
 Most often it will reclaim only the 0th generation. I think it would be
 useful to have something like performFullGC.

Or rather performMajorGC :)

It seems that in GHC it suffices to

foreign import ccall performMajorGC :: IO ()

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Running a final finaliser

2003-12-18 Thread Simon Marlow
 
 I hope this question isn't too stupid, but I can't find
 any obvious way to do this from reading the ghc docs.
 
 What I want to do is call a final foreign function (a
 library shutdown routine) when Haskell terminates, but
 after all ForeignPtr finalisers have been run.

 I suppose I could implement some kind of finaliser
 counter so the last finalizer could tell it was the
 last finaliser and call the shutdown routine, but this
 seems a little awkward, especially as these days the
 FFI requires finalisers to be foreign functions.
 
 The other possibility that occurs to me is that I call
 performGC at the very end of the program, immediately
 before calling the library shutdown routine. But I'm
 not too sure whether that will guarantee that all
 finalizers have been run even if there are no live
 references to foreign objects at that point. (Using
 GC as described in the non-stop Haskell paper it
 seems possible that finalisers won't be run immediately
 in response to performGC.)

Using an explicit reference count sounds fine to me.  The runtime system
doesn't support any ordering constraints between finalizers (it's a
really hard problem in general), so the party line is you have to code
it up yourself.

Actually, I seem to recall that we were going to disable the running of
finalizers at the end of the program completely, in which case you would
have to add your cleanup code in the main thread, with an appropriate
exception handler.

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