
Here's an infinite structure with logarithmic access time with natural numbers for keys. It's not particularily efficient for a sparse map, but if the maximum used key is linear in the size of your problem, it gives log(n) access time. However, an infinite fold of insert is still _|_; you have to construct with "fromAscList" if you want to initialize the map with some infinite data. This is because otherwise there is no way to know that we are "done" with the head of the map; some later value in the list might replace it. The use of the ascending list lets us know after we've passed key n, we can construct the map up to at least n. *NatMap> lookup (fromAscList [(v,v) | v <- [0..]]) 42 Just 42
module NatMap where import Prelude hiding (lookup)
data NatMap v = NatMap (Maybe v) (NatMap v) (NatMap v)
empty :: NatMap v empty = NatMap Nothing empty empty
replace :: Integer -> Maybe v -> NatMap v -> NatMap v replace k v (NatMap e l r) | k < 0 = error "NatMap: negative key" | k == 0 = NatMap v l r | low == 0 = NatMap e (replace high v l) r | otherwise = NatMap e l (replace high v r) where (high,low) = divMod k 2
insert :: Integer -> v -> NatMap v -> NatMap v insert k v = replace k (Just v)
delete :: Integer -> NatMap v -> NatMap v delete k = replace k Nothing
lookup :: NatMap v -> Integer -> Maybe v lookup (NatMap e l r) k | k < 0 = error "NatMap: negative key" | k == 0 = e | low == 0 = lookup l high | otherwise = lookup r high where (high, low) = divMod k 2
fromAscList :: [(Integer, v)] -> NatMap v fromAscList [] = empty fromAscList ((0,_):(0,v):xs) = fromAscList ((0,v):xs) fromAscList ((0,v):xs) = NatMap (Just v) l r where NatMap _ l r = fromAscList xs fromAscList xs = NatMap Nothing (fromAscList xs_l) (fromAscList xs_r) where xs_l = [ (high,v) | (k, v) <- xs, let (high,low) = divMod k 2, low == 0 ] xs_r = [ (high,v) | (k, v) <- xs, let (high,low) = divMod k 2, low == 1 ]
-- ryan