[Haskell-cafe] STM problems

Luke Palmer lrpalmer at gmail.com
Sun Aug 23 05:12:01 EDT 2009


On Sun, Aug 23, 2009 at 1:33 AM, Michael Speer<knomenet at gmail.com> wrote:
> data HashTable a b = HashTable (a -> Int) (STM (Array Int (TVar (Maybe b))))

So wait... a HashTable is a hash function together with an *action
returning an array of TVars?*    I don't think that's right.  It looks
like that action is recreating an empty table each time it is
accessed.  You probably want:

data HashTable a b = HashTable (a -> Int) (TVar (Array Int (TVar (Maybe b))))

instead.  The rest of the implementation will follow the type.

>
> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list