RFC: termination detection for STM

Michael Stahl ms43 at users.sourceforge.net
Wed Feb 14 19:24:40 EST 2007


On Wed, 14 Feb 2007 10:04:32 +0000, Simon Marlow wrote:

> Perhaps I'm missing something, but doesn't GHC already detect the kind of 
> deadlock you're talking about here?  When a thread is blocked and cannot be 
> woken up, it is sent the BlockedOnDeadMVar exception.  It's more precise than
> the extension you propose, because the GC is used to check which threads are 
> unreachable and therefore cannot be woken up, so it can detect mutual-deadlock
> between two threads in a system that contains other running threads.
> 
> If I've misunderstood, please let me know.  Maybe you could knock up a quick 
> example program of the kind of deadlock you want to detect, and see what GHC 
> currently does?

basically, my interpreter has a master thread, several rule threads, match
threads, and delayed threads. the main data structure is the goal store,
which is basically a Map containing some TChans. the master thread must
retain all the rule threads (otherwise there will be no result). actually
i never thought about this before, but it is quite simple: upon
termination, the master thread prints the result goal store, so any
transaction which retries after reading a TVar that is reachable from the
goal store will be kept alive during gc. so if a match thread reads a
logical variable (represented as TVar) which is reachable from the goal
store and then retries, it will never be garbage collected. so i cannot
simply count match threads until none are left by catching
BlockedIndefinitely (which would not be sufficient anyway, as rule threads
can create new ones, creating interesting race conditions).

	michael stahl


PS
here is the simplest thing i could come up with that has threads which are
blocked indefinitely but not gc'd.



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