Michael Hobbs wrote:
> (We're assuming that we can't lock them both simultaneously)

I knew I should have read the literature on deadlock avoidance before
posting that message. :-/  In fact, I should have used the word
"atomically" above instead of "simultaneously". As it turns out, I
believe that assumption was incorrect. That is, it is possible to create
an atomic operation that locks two values, while avoiding deadlock.
Here's my stab at it. (NB: This is simply an off-the-cuff attempt. It
looks like it should work right, but it is far from rigorously tested or
analyzed.)

type PairMVar a = (MVar Bool, IORef a)

takePairMVar :: PairMVar a -> PairMVar b -> IO (a, b)
takePairMVar a@(claimA, refA) b@(claimB, refB) = do
  -- Attempt to lay claim to the A value. This will block if some other
thread
  -- has successfully completed A takePairMVar call using this value.
  aIsClaimed <- takeMVar claimA
  if aIsClaimed then do
    -- Some other thread has snuck in and laid claim to A. Release
claimA and
    -- try again.
    putMVar claimA aIsClaimed
    takePairMVar a b
   else do
    -- Establish our claim on A and release claimA.
    putMVar claimA True
    -- Attempt to lay claim to the B value.
    bIsClaimed <- takeMVar claimB
    -- We need to takeMVar claimA regardless of whether bIsClaimed or
not.
    -- At this point, we have a lock on claimB and are attempting to
lock
    -- claimA. If some other thread has a lock on claimA and is
attempting to
    -- lock claimB, we have a deadlock. However, this should never
happen since
    -- we have established our claim on A so no other thread should have
claimA
    -- locked indefinitely.
    takeMVar claimA
    if bIsClaimed then do
      -- Some other thread has snuck in and laid claim to B. Relinquish
all of
      -- our claims and try again.
      putMVar claimA False
      putMVar claimB bIsClaimed
      takePairMVar a b
     else do
      -- We have successfully locked claimA and claimB. We never
explicitly set
      -- claimB to True, since we have implicitly claimed it by keeping
it
      -- locked.
      valA <- readIORef refA
      valB <- readIORef refB
      return (valA, valB)

putPairMVar :: PairMVar a -> PairMVar b -> a -> b -> IO ()
putPairMVar (claimA, refA) (claimB, refB) a b = do
  -- Fairly straightforward. Write the values and relinquish all claims.
  writeIORef refA a
  writeIORef refB b
  putMVar claimA False
  putMVar claimB False
  return ()

Reply via email to