[Haskell-cafe] STM problems
Michael Speer
knomenet at gmail.com
Sun Aug 23 03:33:12 EDT 2009
I am playing a writing a simple STM hashtable. I expected the
following code to alter the TVars in it, but they appear immutable. I
assume I am simply doing something wrong, but I am not sure what it
is. Any pointers would be greatly appreciated.
import Control.Concurrent.STM
import Control.Concurrent
import Array
data HashTable a b = HashTable (a -> Int) (STM (Array Int (TVar (Maybe b))))
mkHashTable :: ( a -> Int ) -> Int -> HashTable a b
mkHashTable hashfn numBuckets | numBuckets > 0 = do
HashTable hashfn $ do
vs <- mapM (\v -> newTVar Nothing >>= \tv -> return (v,tv) ) [1..numBuckets]
return $ array (1,numBuckets) vs
readHashTable :: HashTable a b -> a -> STM (Maybe b)
readHashTable hashtable key =
let (HashTable hashfn table) = hashtable
in table >>= \tb -> readTVar (tb ! hashfn key)
writeHashTable :: HashTable a b -> a -> (Maybe b) -> STM ()
writeHashTable hashtable key value =
let (HashTable hashfn table) = hashtable
in table >>= \tb -> writeTVar (tb ! hashfn key) value >> return ()
main = let ht = mkHashTable id 10 :: HashTable Int String
in do
v <- atomically $ do
mapM_ (\n -> writeHashTable ht n (Just $ "hello " ++ show
n)) [1..10]
mapM (\n -> readHashTable ht n) [1..10]
print v
More information about the Haskell-Cafe
mailing list