
Hi, I need a rather strange data structure, and I can't find any existing implementations or think of a way to implement it. It's a "multiqueue", basically a map of queues. The trick is that it should be lazy in its spine and still support efficient access. For example, the following should hold: dequeue 1 (foldr (enqueue 1) empty [42..]) = Just (42, ...) (where dequeue :: k -> QMap k v -> Maybe (v, QMap k v), similarly for enqueue) I also need a unionWith :: ([v] -> [v] -> [v]) -> QMap k v -> QMap k v -> QMap k v. I realize that these might be some pretty tough requirements to meet. Any pointers or original ideas? Thanks, Luke

On Tue, Oct 21, 2008 at 11:43 AM, Luke Palmer
Hi, I need a rather strange data structure, and I can't find any existing implementations or think of a way to implement it. It's a "multiqueue", basically a map of queues. The trick is that it should be lazy in its spine and still support efficient access. For example, the following should hold:
This doesn't answer your question, but how is a Map of queues not "spine-lazy"? I'm mostly looking to understand that term. Justin

On Tue, Oct 21, 2008 at 3:02 PM, Justin Bailey
On Tue, Oct 21, 2008 at 11:43 AM, Luke Palmer
wrote: Hi, I need a rather strange data structure, and I can't find any existing implementations or think of a way to implement it. It's a "multiqueue", basically a map of queues. The trick is that it should be lazy in its spine and still support efficient access. For example, the following should hold:
This doesn't answer your question, but how is a Map of queues not "spine-lazy"? I'm mostly looking to understand that term.
Well, first, my question was highly malformed. I actually just want a spine lazy map of lists; queues were not what I wanted. Data.Map is strict in its keys, meaning rougly that you cannot store infinitely many keys in a map. So: foldr (\x x -> Map.insert x x) Map.empty [0..] = _|_ I.e. if you take this map that maps every natural to itself and try to do anything with it, you will get an infinite loop (or stack overflow, or whatever). On the other hand, the "map" type [(k,v)] *is* spine lazy, because, for example: lookup 42 [ (x,x) | x <- [0..] ] = Just 42 It's just not very efficient. I'm basically looking for a version of the above which has a logarithmic lookup time. The best I've come up with so far is a binary search tree where the most recently inserted thing is at the root. It's not balanced, because balancing would make it strict (as far as I can tell). So it's only logarithmic time sometimes. Luke

On 10/21/08, Luke Palmer
Well, first, my question was highly malformed. I actually just want a spine lazy map of lists; queues were not what I wanted. [...] The best I've come up with so far is a binary search tree where the most recently inserted thing is at the root. It's not balanced, because balancing would make it strict (as far as I can tell). So it's only logarithmic time sometimes.
Surely a trie would do the job? With each node a map? One could probably even produce a Patricia trie at some constant cost to keep things on the order of number of elements (ish)rather than on the order of length of elements. Either way its not exactly going to be log (n) but depending on what you're storing it might be as efficient if not more so, and indeed would let you be lazy in the amount of each key consumed (assuming keys are, e.g., lists and not ints) as well as in the spine. --Sterl.

On Wed, 22 Oct 2008 11:54:50 Luke Palmer wrote:
On Tue, Oct 21, 2008 at 3:02 PM, Justin Bailey
wrote: On Tue, Oct 21, 2008 at 11:43 AM, Luke Palmer
wrote: Hi, I need a rather strange data structure, and I can't find any existing implementations or think of a way to implement it. It's a "multiqueue", basically a map of queues. The trick is that it should be lazy in its spine and still support efficient access. For example, the following should hold:
This doesn't answer your question, but how is a Map of queues not "spine-lazy"? I'm mostly looking to understand that term.
Well, first, my question was highly malformed. I actually just want a spine lazy map of lists; queues were not what I wanted.
Data.Map is strict in its keys, meaning rougly that you cannot store infinitely many keys in a map. So:
foldr (\x x -> Map.insert x x) Map.empty [0..] = _|_
I.e. if you take this map that maps every natural to itself and try to do anything with it, you will get an infinite loop (or stack overflow, or whatever).
On the other hand, the "map" type [(k,v)] *is* spine lazy, because, for example:
lookup 42 [ (x,x) | x <- [0..] ] = Just 42
It's just not very efficient. I'm basically looking for a version of the above which has a logarithmic lookup time.
The best I've come up with so far is a binary search tree where the most recently inserted thing is at the root. It's not balanced, because balancing would make it strict (as far as I can tell). So it's only logarithmic time sometimes.
Luke _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
You might possibly be able to get a logarithmic lookup time for keys known to be present while preserving some laziness (don't ask me how) but to say a key does not exist in the map you would have to somehow check them all, which with an infinite list of keys will never complete. You're unlikely to get a free lunch with infinite maps - infinite items means infinite depth to any tree structure and there are few other nice alternatives. You could simply add your own laziness - have a special map which consumes a list of (key, value) pairs and where reading the map also returns another map evaluated enough to answer the immediate query. Reading an already discovered key will take logarithmic time while reading an undiscovered key will take as long as it takes to find it in the list (for a nonexistent key, until memory runs out). You could also work carefully with mutable references inside the map to make it appear pure from the outside. It could still present a referentially transparent interface since it is only evaluating itself further, not changing what it actually contains. You would have to make sure this worked properly though. With that map you could perform updates as normal. Reading a value from the input list that already exists in the map would just do nothing. I was interested enough to give this a try. Source is attached. It's incomplete - if you finish it please send me the result. Otherwise, use as you like. Cheers, Tim

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

On Wed, Oct 22, 2008 at 3:14 AM, Ryan Ingram
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.
Well, actually the infinite fold of inserts is possible, since: lookup k (insert k x (insert k y)) = x So the "earlier" one overwrites the "later" one in a right fold.
*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)
Thanks for the ideas and inspiration everybody. I was so locked into the Ord constraint that I didn't see the obvious trie alternative. I ended up going with something very similar to Ryan's suggestion. module NatTrie (NatTrie, uniform, modify, lookup, union) where import Prelude hiding (lookup) data NatTrie v = NatTrie { ntVal :: v, nt0 :: NatTrie v, nt1 :: NatTrie v } uniform x = let r = NatTrie x r r in r modify = go . bits where go [] ~(NatTrie x l r) = NatTrie (f x) l r go (False:xs) ~(NatTrie x l r) = NatTrie x (go xs l) r go (True;xs) ~(NatTrie x l r) = NatTrie x l (go xs r) lookup = go . bits where go [] = ntVal go (False:xs) = go xs . nt0 go (True:xs) = go xs . nt1 union f (NatTrie x l r) (NatTrie x' l' r') = NatTrie (F x x') (union f l l') (union f r r') bits x | x < 0 = error "negative key" | otherwise = natBits x natBits 0 = [] natBits x = toBool r : natBits q where (q,r) = quotRem x 2 toBool = (== 1) This does supports the infinite fold. I put the main four operations in class with a fundep for the key, but I'm not totally happy with it. In particular, I couldn't even write SumTrie (with Eithers as keys) without undecidable instances. Ideas for how to make such tries composable would encourage me to release a hackage module :-) Thanks everybody! Luke

Ideas for how to make such tries composable would encourage me to release a hackage module :-)
Have a look at code.haskell.org/gmap/api - a library for composable maps. It currently requires huge instances in the name of efficiency but I hope to improve that over the next couple of months. The basic idea is pretty simple: class Map mp k | mp -> k where lookup :: k -> mp a -> Maybe a etc data EitherMap mpL mpR kL kR = EitherMap mpL mpR instance (Map mpL kL, Map mpR kR) => Map (EitherMap mpL mpR kL kR) where lookup (Left l) (EitherMap mpL mpR) = lookup l mpL lookup (Right r) (EitherMap mpL mpR) = lookup r mpR The types can get a bit hairy at the moment but using associated types instead of fundeps will probably improve that. For lazy spined maps, lookup 'skew binary random access lists' (in Okaski's book, if you have a copy). You'll get roughly the same perfomance as a trie over bits but with the advantage that you can take the tail in constant time. That way, if your keys are time values (I'm guessing this is related to your frp ideas) you get the same garbage collection properties as a simple list of [(Time,a)] but you can still look ahead efficiently. If you have problems with sparse time values you could compose the random access list with something else: data TimeMap mp a = TM (RandList (mp a)) instance (Map mp Integer) => Map (TimeMap mp) Integer where lookup k (TM randList) = lookup k (lookup (div k chunkSize) randList) etc
participants (6)
-
Jamie Brandon
-
Justin Bailey
-
Luke Palmer
-
Ryan Ingram
-
Sterling Clover
-
Timothy Goddard