[Haskell-cafe] When are MVars better than STM?

Thomas Koster tkoster at gmail.com
Sun Jan 24 07:13:27 UTC 2016


On Sun, Jan 24, 2016 at 12:46 AM, Thomas Koster <tkoster at gmail.com> wrote:
> Using Criterion, I have been running benchmarks to measure the
> relative performance of STM and MVars for some simple transactions
> that I expect will be typical in my application. I am using GHC 7.10.2
> and libraries as at Stackage LTS 3.2.
>
> I have found that STM is faster than MVars in all my benchmarks,
> without exception. This seems to go against accepted wisdom [1][2][3].
> I have not included my source code here to save space, but if you
> suspect that I am using MVars incorrectly, just say so and I will post
> my source code separately.
>
> I have two questions:
>
> 1. When are MVars faster than STM? If the answer is "never", then when
> are MVars "better" than STM? (Choose your own definition of "better".)
>
> 2. When given two capabilities (+RTS -N2), MVars are suddenly an order
> of magnitude slower than with just one capability. Why?


On 24 January 2016 at 17:55, Christopher Allen <cma at bitemyapp.com> wrote:
> Could you post the code please?


module Main (main) where

import Control.Concurrent.Async
import Control.Concurrent.MVar
import Control.Concurrent.STM
import Control.Monad
import Criterion.Main

main =
  defaultMain
    [
      bgroup "thrash"
        [
          bench "MVar" $ whnfIO (thrashTest mvarNew mvarInc mvarGet),
          bench "TVar" $ whnfIO (thrashTest tvarNew tvarInc tvarGet)
        ]
    ]

thrashTest :: IO a
           -> (a -> IO ())
           -> (a -> IO b)
           -> IO b
thrashTest new inc get = do
  var <- new
  threads <- replicateM 4 (async (replicateM_ 100000 $ inc var))
  forM_ threads wait
  get var

mvarNew :: IO (MVar Int)
mvarNew = newMVar 0

mvarInc :: MVar Int -> IO ()
mvarInc var =
  modifyMVar_ var $ \ i ->
    return $! succ i

mvarGet :: MVar Int -> IO Int
mvarGet = readMVar

tvarNew :: IO (TVar Int)
tvarNew = newTVarIO 0

tvarInc :: TVar Int -> IO ()
tvarInc var =
  atomically $ do
    i <- readTVar var
    writeTVar var $! succ i

tvarGet :: TVar Int -> IO Int
tvarGet = readTVarIO

--
Thomas Koster


More information about the Haskell-Cafe mailing list