Skip to content

Instantly share code, notes, and snippets.

@zouppen
Created November 18, 2011 13:17
Show Gist options
  • Save zouppen/1376433 to your computer and use it in GitHub Desktop.
Save zouppen/1376433 to your computer and use it in GitHub Desktop.
A quick and sparse wrapping of Map to Software Transactional Memory. You can extend this to cover all features of Map easily. Useful for key-value storage where you otherwise need to signal the changes somehow. Now this is done automatically in STM. This
module TransactionalMap where
import Control.Concurrent.STM
import Control.Monad (unless)
import Data.Map (Map)
import qualified Data.Map as M
type TransactionalMap k a = TVar (Map k a)
newEmptyTransactionalMap :: STM (TransactionalMap k a)
newEmptyTransactionalMap = newTVar M.empty
newEmptyTransactionalMapIO :: IO (TransactionalMap k a)
newEmptyTransactionalMapIO = newTVarIO M.empty
-- |Like Data.Map.insert, inserts a value into map, replacing old key if present.
insert :: Ord k => TransactionalMap k a -> k -> a -> STM ()
insert m k a = do
cur <- readTVar m
writeTVar m $ M.insert k a cur
-- |Tries to take value associated with the key. If key isn't there,
-- map is not modified and Nothing is returned. Otherwise it removes
-- the key from the map and returns the value it is associated with.
tryGet :: Ord k => TVar (Map k a) -> k -> STM (Maybe a)
tryGet m k = do
cur <- readTVar m
writeTVar m $ M.delete k cur -- No harm if not present.
return $ M.lookup k cur
-- |Gets a value from transactional map. If key is not there, this
-- will retry.
get :: Ord k => TVar (Map k a) -> k -> STM a
get m k = do
cur <- readTVar m
unless (M.member k cur) retry
writeTVar m $ M.delete k cur -- No harm if not present.
return $ cur M.! k
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment