addFinalizer & ThreadId

Volker Stolz vs@foldr.org
Wed, 28 Aug 2002 14:45:38 +0200


I remember that addFinalizer never did work quite the way people
expected it to. A current instantiation of this problem: adding
a finalizer to a ThreadId. Could somebody please give me a short
explanation why the following never prints "Finalize"?
[ghc is 5.04-cvs]

\begin{code}
module Main where

import IO
import Concurrent
import GHC.Weak

main = do
  mv <- newEmptyMVar
  child <- forkIO $ do
    takeMVar mv
    print "terminated"
  addFinalizer child fin
  putMVar mv ()
  yield
  yield
  yield
  threadDelay $ 1000*1000*30
  print "done"

fin :: IO ()
fin = do
  print "Finalize"
\end{code}
-- 
http://www-i2.informatik.rwth-aachen.de/stolz/ *** PGP *** S/MIME