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

Ryan Yates fryguybob at gmail.com
Sun Jan 24 14:04:17 UTC 2016


Hi Thomas,

I'm sorry I don't have time right now for a proper response (buried under
paper deadlines).  There are certainly times when one will be faster then
the other and the reasons are quite complicated.  To complicate matters
further it is very difficult to get benchmarks that don't lie about
performance in this space.  There are also alternative implementations that
change the balance drastically.  The only broad advice I can give is to
benchmark the target application with both implementations to see how all
the implications fall out.  A broad description of the differences in
implementation would be that MVars have a fairness guarantee (that does not
come for free) for waking waiting threads.  STM does not have this fairness
which can lead to problems for programs that have quick transactions that
always win over occasional long transactions (there are ways to avoid with
a different implementation or with the cost of shifted to the programmer).
My guess is in your particular benchmark the unfairness of STM works to
your advantage and all the work is happening sequentially while the MVar
version's fairness incurs frequent cache misses.


Ryan

On Sun, Jan 24, 2016 at 2:13 AM, Thomas Koster <tkoster at gmail.com> wrote:

> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160124/83b28690/attachment.html>


More information about the Haskell-Cafe mailing list