Hello Kamil,

Monday, June 22, 2009, 12:01:40 AM, you wrote:

> Right... Python uses hashtables while here I have a tree with log n

you can try this pure hashtable approach:

import Prelude hiding (lookup)
import qualified Data.HashTable
import Data.Array
import qualified Data.List as List


data HT a b = HT (a->Int) (Array Int [(a,b)])

-- size is the size of array (we implent closed hash)
-- hash is the hash function (a->Int)
-- list is assoclist of items to put in hash
create size hash list = HT hashfunc
                           (accumArray (flip (:))
                                       []
                                       (0, arrsize-1)
                                       (map (\(a,b) -> (hashfunc a,b)) list)
                           )

  where arrsize     =  head$ filter (>size)$ iterate (\x->3*x+1) 1
        hashfunc a  =  hash a `mod` arrsize


lookup a (HT hash arr) = List.lookup a (arr!hash a)


main = do let assoclist = [("one", 1), ("two", 2), ("three", 3)]
              hash = create 10 (fromEnum . Data.HashTable.hashString) assoclist
          print (lookup "one" hash)
          print (lookup "zero" hash)



-- 
Best regards,
 Bulat                            mailto:bulat.zigans...@gmail.com

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to