
On 19 January 2011 20:50, Edward Z. Yang
+1 for reverting to using an IORef.
Here's a hastily constructed benchmark (based on the one from #3838) that compares the two implementations: {-# LANGUAGE BangPatterns #-} module Main where import Control.Concurrent.STM.TVar import Control.Monad.STM import Control.Concurrent.MVar import Control.Concurrent import Control.Monad import Foreign import Data.IORef newtype Unique = Unique Integer deriving (Eq, Ord) -- Current implementation of Unique using TVars uniqSource :: TVar Integer uniqSource = unsafePerformIO (newTVarIO 0) {-# NOINLINE uniqSource #-} newUnique :: IO Unique newUnique = atomically $ do val <- readTVar uniqSource let next = val+1 writeTVar uniqSource $! next return (Unique next) -- New implementation of Unique using IORefs uniqSource' :: IORef Integer uniqSource' = unsafePerformIO (newIORef 0) {-# NOINLINE uniqSource' #-} newUnique' :: IO Unique newUnique' = do !next <- atomicModifyIORef uniqSource' $ \val -> let !next = val+1 in (next, next) return (Unique next) -- Benchmark numThreads :: Integer numThreads = 1000000 bench doNewUnique = do done <- newEmptyMVar let loop :: Integer -> IO () loop i = do when (i < numThreads) $ do forkIO $ do threadDelay 1000 Unique u <- doNewUnique when (u == numThreads) $ putMVar done () loop (i + 1) loop 0 takeMVar done main = bench newUnique main = bench newUnique' (Build with -O2) $ time ./benchUniqueTVar real 0m16.575s user 0m16.080s sys 0m0.430s $ time ./benchUniqueIORef real 0m16.378s user 0m15.840s sys 0m0.480s So using an IORef is a tiny bit faster. Does newUniqueSTM give you a performance advantage in a STM transaction? Or is it just a convenience that you don't need to use unsafeIOToSTM? Because of the slightly simpler implementation and slightly better performance I'm for reverting to IORefs. Regards, Bas