RFC: termination detection for STM
Simon Marlow
simonmarhaskell at gmail.com
Thu Feb 15 05:38:53 EST 2007
Michael Stahl wrote:
> here is the simplest thing i could come up with that has threads which are
> blocked indefinitely but not gc'd.
>
This example isn't deadlocked: it just waits 10 seconds and then receives the
BlockedIndefinitely exception. Can you construct an example that has a real
deadlock that isn't detected?
Cheers,
Simon
>
> module Main where
> import Control.Monad.STM
> import Control.Concurrent.STM.TVar
> import Control.Concurrent.STM.TChan
> import Control.Concurrent
>
> type Store' = TChan (TVar Int)
>
> main = do
> (store,store') <- atomically $ do
> c <- newTChan
> c' <- dupTChan c
> v <- newTVar 0
> writeTChan c v
> return (c,c')
> forkIO $ rule store
> threadDelay 10000000 -- wait for termination
> print' store'
> where
> rule store = do
> x <- atomically $
> readTChan store
> forkIO $ match x
> rule store
> match x = do
> atomically $ do
> readTVar x
> retry
> print' store = do
> x <- atomically $ do
> v <- readTChan store
> readTVar v
> print x
> print' store
More information about the Glasgow-haskell-users
mailing list