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

Thomas Koster tkoster at gmail.com
Thu Jan 28 05:54:58 UTC 2016


On 24 January 2016 at 17:46, Thomas Koster <tkoster at gmail.com> wrote:
> I have found that STM is faster than MVars in all my benchmarks,
> without exception. This seems to go against accepted wisdom.

On 24 January 2016 at 18:13, Thomas Koster <tkoster at gmail.com> wrote:
> 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

On 28 January 2016 at 16:26, John Lato <jwlato at gmail.com> wrote:
> This has nothing to do with your questions, but are you sure that mvarInc is
> sufficiently strict?

I think so. If you think it isn't, I would love to know why, since
strictness and correct use of seq are still a bit of a black art for
me.

The strictness characteristics of the MVar version and the STM version
as written ought to be identical. If not, I would love to know why as
well.

--
Thomas Koster


More information about the Haskell-Cafe mailing list