RE: Running a "final" finaliser

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

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

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

On Wednesday 31 Dec 2003 8:56 am, Adrian Hey wrote:
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).
Sorry, I should clarify this. The error does not occur when killLibRef is called, it occurs sometime after that (during the final rts cleanup and execution of any outstanding finalisers I guess). Regards -- Adrain Hey

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 :-) Regards -- 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
participants (2)
-
Adrian Hey
-
Simon Marlow