Ketil Malde wrote:
So the naïve attempt at doing this would be something like:

    thread = do
        -- grab "lock 1"
        t <- readTVar lock
        when t retry
        writeTVar lock True

        -- grab "lock 2"
        t2 <- readTVar lock2
        when t2 retry writeTVar
        writeTVar lock2 True

        -- do something
        writeTVar lock2 False
        writeTVar lock False

and another one with the locks reversed.  But that won't work of
course, since the 'retry' will rollback the taking of lock 1 as well.
So do I need to split this up into separate STM transactions and
orchestrate the locking from the IO monad?
Indeed:

type Lock = TVar Bool

claim :: Lock -> IO ()
claim tv = atomically $ do
 b <- readTVar tv
 when b retry
 writeTVar tv True

release :: Lock -> IO ()
release tv = atomically $ writeTVar tv False

Writing a lock in STM is not useful for the purpose of doing some other STM stuff inbetween anyway, because that goes against the point of STM (you don't need locks for STM actions -- as you point out, the rollback from the locks is not useful in your example). So it only makes sense if you are doing some other IO action inbetween the claim and release. For example, you might want to write to a socket from several threads, and use locks to ensure exclusivity.

Often, using STM for locks is pretty silly because there is some other way to do it (e.g. have the threads write their packets to an STM queue, and have a single thread reading from the queue and sending on the sockets) but they're a simple example of how you can create deadlock in STM, e.g.

main = do
 tv1 <- newTVarIO False
 tv2 <- newTVarIO False
 forkIO $ claim tv2 >> claim tv1 >> release tv1 >> release tv2
 claim tv1 >> claim tv2 >> release tv2 >> release tv1

is a possible source of deadlock, or even the more straightforward:

main = newTVarIO True >>= claim

What is particularly cool about Haskell's STM implementation is that in the second example (and possibly in the first one too) the run-time can detect straight-out deadlock and will throw you a deadlock exception. It does this via garbage collection -- if a thread is waiting on a TVar that no other thread has a reference to, the thread is technically ripe for garbage collection and the thread is instead woken up with an exception. At least, I think that's the principle. I don't think it can catch all cases (another thread may have the reference but may never use it) but it's still quite impressive.

Thanks,

Neil.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to