Bug in touchForeignPtr?
Keean Schupke
k.schupke at imperial.ac.uk
Wed Nov 24 06:03:47 EST 2004
Is that true... what about:
>module Main where
>
>import Control.Concurrent.MVar
>import System.Mem.Weak
>
>myFinalizer :: MVar () -> IO ()
>myFinalizer m = do
> putMVar m ()
> return ()
>
>createMyFinalizer :: IO (MVar (),Weak ())
>createMyFinalizer = do
> m <- newMVar ()
> w <- mkWeakPtr () (Just (myFinalizer m))
> return (m,w)
>
>main :: IO ()
>main = do
> (m,_) <- createMyFinalizer
> _ <- takeMVar m
> return ()
Keean
Duncan Coutts wrote:
>On Tue, 2004-11-23 at 18:01 +0100, Peter Simons wrote:
>
>
>>Simon Marlow writes:
>>
>> >>> Note that the GC only starts the finaliser thread. The
>> >>> program can still terminate before this thread has run
>> >>> to completion [...]
>>
>> > If you want anything else, you can implement it.
>>
>>How do I implement that particular feature? I don't see how
>>I could write a 'main' function that waits for the finalizer
>>thread having terminated.
>>
>>
>
>For all normal threads you can wait for them by making them write to an
>MVar when they finish and the main thread waits to read from the MVar
>before finishing itself.
>
>Of course for the finalizer thread you cannot do this since you did not
>start it. However the fact that finalizers are run in a dedicated thread
>is itself an implementation detail that you have no control over anyway.
>
>Obviously from what Simon has said, you cannot solve the finalisers
>problem just by running the finaliser thread to completion (or it'd be
>done that way already!)
>
>Duncan
>
>_______________________________________________
>Glasgow-haskell-users mailing list
>Glasgow-haskell-users at haskell.org
>http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
More information about the Glasgow-haskell-users
mailing list