[Haskell-cafe] Lock-Free Data Structures using STMs in Haskell

Pete Kazmier pete-expires-20080608 at kazmier.com
Wed Apr 9 09:50:27 EDT 2008


I recently read the STM paper on lock-free data structures [1] which I
found very informative in my quest to learn how to use STM.  However,
there are a few things I do not fully understand and was hoping
someone might be able to explain further.

In the STM version of the ArrayBlockingQueue, the following type is
defined:

  data ArrayBlockingQueueSTM e = ArrayBlockingQueueSTM {
    shead :: TVar Int,
    stail :: TVar Int,
    sused :: TVar Int,
    slen :: Int,
    sa :: Array Int (TVar e)
  }

It's unclear to me why the Array's elements must be wrapped in TVars.
Why aren't the TVars on shead, stail, and sused sufficient?  Here is
the only function that reads from the queue:

  readHeadElementSTM :: ArrayBlockingQueueSTM e
                        -> Bool -> Bool -> STM (Maybe e)
  readHeadElementSTM abq remove block
    = do u <- readTVar (sused abq)
         if u == 0
            then if block
                    then retry
                    else return Nothing
            else do h <- readTVar (ihead abq)
                 let tv = sa abq ! h
                 -- Why are the array elements wrapped in TVars?
                 e <- readTVar tv
                 if remove
                    then do
                      let len = slen abq
                      let newh = h `mod` len
                      writeTVar (shead abq) $! newh
                      writeTVar (sused abq) $! (u-1)
                    else return ()
                 return (Just e)

It is not immediately obvious to me why the elements need to be
wrapped in TVars.  Could someone help elaborate?

The other question is in regards to section 2 where STM is
introduced.  The authors define the following:

  decT :: TVar Int -> IO ()
  decT v = atomically (do x <- readTVar v
                          if x == 0
                             then retry
                             else return ()
                          writeTVar v (x-1))

And then go on to show how easy it is to compose STM types with this
function:

  decPair v1 v1 :: TVar Int -> TVar Int -> IO ()
  decPair v1 v2 = atomically (decT v1 `orElse` decT v2)

Will this actually compile?  I was under the impression that 'orElse'
could only combine STM types, not IO () types.  

Thank you,
Pete

[1] Anthony Discolo, Tim Harris, Simon Marlow, Simon Peyton Jones, and
Satnam Singh. Lock-free data structures using STMs in Haskell. In
Eighth International Symposium on Functional and Logic Programming
(FLOPS.06), April 2006.



More information about the Haskell-Cafe mailing list