
Is there a data type that's spine lazy like a list, but can be seeked (sought?) efficiently? IntMap and Sequence are spine strict so if you take the head element all the elements are forced even if their contents are not. E.g., 'Sequence.index (Sequence.fromList [0..]) 0' will diverge, but obviously 'head [0..]' won't. I can get what I want from a list of lists where the outer list is is 'iterate (drop n)' on the inner one... this is a kind of skip list, right? It seems like it should be possible to generalize this to multiple levels with increasing skip amounts, then I can seek relatively efficiently and won't force the spine beyond where I seek. Effectively, this is nested list like [[[a]]], where each level above the bottom is something like 'iterate (drop n) level_below'. Alternately, it should also be possible to do something fancy like a self-modifying data structure that constructs its index as you force bits of it, but this would require some hairy unsafePerformIO, I think. Has anyone heard of a data structure like this, either the plain list of lists or the self modifying magic one? Surely efficiently indexing a lazy list is something someone else has thought about? It looks like Luke Palmer's data-inttrie might be doing this, though it's not clear from the documentation. It looks like it lacks emptiness, so it doesn't apply to finite structures. lazyarray looks like it might be doing the magic self-modifying thing, though it wants a a static bounds right off the bat, which isn't much help when the whole point is to avoid having to figure out how long the input is.

Hmmmm.... {-# LANGUAGE GADTs, EmptyDataDecls, KindSignatures #-} data Z :: * data S :: * -> * ---------------------------------------------------------------------- data SkipList s a where Empty :: SkipList s a Cons :: Element (S s) a -> SkipList (S s) a -> SkipList s a instance Show a => Show (SkipList s a) where showsPrec d Empty = showString "Empty" showsPrec d (Cons elm xs) = showParen (d > 10) $ showString "Cons " . showsPrec 11 elm . (' ':) . showsPrec 11 xs ---------------------------------------------------------------------- data Element s a where None :: Element s a Branch :: !Int -> a -> Element s a -> Element s a -> Element (S s) a instance Show a => Show (Element s a) where showsPrec d None = showString "None" showsPrec d (Branch sz x l r) = showParen (d > 10) $ showString "Branch " . showsPrec 11 sz . (' ':) . showsPrec 11 x . (' ':) . showsPrec 11 l . (' ':) . showsPrec 11 r sizeE :: Element s a -> Int sizeE None = 0 sizeE (Branch n _ _ _) = n branch :: a -> Element s a -> Element s a -> Element (S s) a branch x l r = Branch (sizeE l + sizeE r + 1) x l r ---------------------------------------------------------------------- fromList :: ElementFromList s => [a] -> SkipList s a fromList [] = Empty fromList xs = let (elm, xs') = elementFromList xs in Cons elm (fromList xs') class ElementFromList s where elementFromList :: [a] -> (Element s a, [a]) instance ElementFromList Z where elementFromList xs = (None, xs) instance ElementFromList s => ElementFromList (S s) where elementFromList [] = (None, []) elementFromList (x:xs) = let (elmL, xsL) = elementFromList xs (elmR, xsR) = elementFromList xsL in (branch x elmL elmR, xsR) ---------------------------------------------------------------------- toList :: SkipList s a -> [a] toList Empty = [] toList (Cons elm xs) = go elm (toList xs) where go :: Element s a -> [a] -> [a] go None rest = rest go (Branch _ x l r) rest = x : go l (go r rest) ---------------------------------------------------------------------- class Nth s where nth :: Element s a -> Int -> Either Int a instance Nth Z where nth None i = Left i instance Nth s => Nth (S s) where nth None i = Left i nth (Branch n x l r) i | i == 0 = Right x | i >= n = Left (i-n) | otherwise = either (nth r) Right $ nth l (i-1) index :: Nth s => SkipList s a -> Int -> Maybe a index Empty _ = Nothing index (Cons elm xs) i = either (index xs) Just $ nth elm i -- Felipe.

Oh, an example: *Main> fromList [1..8] :: SkipList Z Int Cons (Branch 1 1 None None) (Cons (Branch 3 2 (Branch 1 3 None None) (Branch 1 4 None None)) (Cons (Branch 4 5 (Branch 3 6 (Branch 1 7 None None) (Branch 1 8 None None)) None) Empty)) *Main> fromList [1..8] :: SkipList (S Z) Int Cons (Branch 3 1 (Branch 1 2 None None) (Branch 1 3 None None)) (Cons (Branch 5 4 (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None)) (Branch 1 8 None None)) Empty) *Main> fromList [1..8] :: SkipList (S (S Z)) Int Cons (Branch 7 1 (Branch 3 2 (Branch 1 3 None None) (Branch 1 4 None None)) (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None))) (Cons (Branch 1 8 None None) Empty) *Main> let x = fromList [1..8] :: SkipList Z Int *Main> toList x [1,2,3,4,5,6,7,8] *Main> x `index` 3 Just 4 *Main> x `index` 8 Nothing Cheers! =) -- Felipe.

On 20 August 2010 13:29, Felipe Lessa
Oh, an example:
*Main> fromList [1..8] :: SkipList Z Int Cons (Branch 1 1 None None) (Cons (Branch 3 2 (Branch 1 3 None None) (Branch 1 4 None None)) (Cons (Branch 4 5 (Branch 3 6 (Branch 1 7 None None) (Branch 1 8 None None)) None) Empty)) *Main> fromList [1..8] :: SkipList (S Z) Int Cons (Branch 3 1 (Branch 1 2 None None) (Branch 1 3 None None)) (Cons (Branch 5 4 (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None)) (Branch 1 8 None None)) Empty) *Main> fromList [1..8] :: SkipList (S (S Z)) Int Cons (Branch 7 1 (Branch 3 2 (Branch 1 3 None None) (Branch 1 4 None None)) (Branch 3 5 (Branch 1 6 None None) (Branch 1 7 None None))) (Cons (Branch 1 8 None None) Empty)
*Main> let x = fromList [1..8] :: SkipList Z Int *Main> toList x [1,2,3,4,5,6,7,8] *Main> x `index` 3 Just 4 *Main> x `index` 8 Nothing
How about fromList [1..] like Evan's original email had (which I think is going to be a problem here as well)? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, Aug 20, 2010 at 12:49 AM, Ivan Lazar Miljenovic
How about fromList [1..] like Evan's original email had (which I think is going to be a problem here as well)?
The only "problem" is that the Element's sizes will be forced up to the point you need, but not anymore. *Main> (fromList [1..] :: SkipList Z Int) `index` 100 Just 101 Probably this small problem could be removed if the code was polished. Alas, the idea is simple. Each 'Element' contains up to 2^(s-1) data. For example, with an 'Element Z a' you can't store anything. With an 'Element (S Z) a' you may store zero or one datum. With an 'Element (S (S Z)) a', you may store between 0 and 4 data, and so forth. Then we just create an SkipList so that the Elements have an increasing capacity. When you 'Cons', the 'Element' of tail of the SkipList will have twice more capacity than the 'Element' of the head. However, I haven't thought about how operations such as 'cons' and 'tail' would be implemented =). OP just asked about indexing ;-). Cheers! =D -- Felipe.

On Fri, Aug 20, 2010 at 12:57 AM, Felipe Lessa
Alas, the idea is simple. Each 'Element' contains up to 2^(s-1) data. For example, with an 'Element Z a' you can't store anything. With an 'Element (S Z) a' you may store zero or one datum. With an 'Element (S (S Z)) a', you may store between 0 and 4 data, and so forth.
Erm, correcting myself: Alas, the idea is simple. Each 'Element' contains up to (2^s)-1 data. For example, with an 'Element Z a' you can't store anything. With an 'Element (S Z) a' you may store zero or one datum. With an 'Element (S (S Z)) a', you may store between 0 and 3 data. With an 'Element (S (S (S Z))) a', you may store between 0 and 7 data, and so forth. Cheers! =) -- Felipe.

However, I haven't thought about how operations such as 'cons' and 'tail' would be implemented =). OP just asked about indexing ;-).
Hah, serves me right I suppose. I figured the promise of some type fanciness would be catnip to some well-typed cats out there, but your implementation is even more advanced than I expected. I'll have to squint at it a while to figure out how it works and how the usual list ops could be implemented. Thanks for giving me something to chew on! And thanks too for the example of how to write a showsPrec, I hadn't figured that out yet!

On Thu, Aug 19, 2010 at 9:57 PM, Felipe Lessa
However, I haven't thought about how operations such as 'cons' and 'tail' would be implemented =). OP just asked about indexing ;-).
Well if all you need is indexing, then an integer trie does it, right? http://hackage.haskell.org/package/data-inttrie Luke

On Fri, Aug 20, 2010 at 3:57 AM, Luke Palmer
On Thu, Aug 19, 2010 at 9:57 PM, Felipe Lessa
wrote: However, I haven't thought about how operations such as 'cons' and 'tail' would be implemented =). OP just asked about indexing ;-).
Well if all you need is indexing, then an integer trie does it, right? http://hackage.haskell.org/package/data-inttrie
Probably! More specifically, newtype SkipList a = (Int, IntTrie a) index :: SkipList a -> Int -> Maybe a index i (n, t) = if i < n && i >= 0 then Just (apply t i) else Nothing However, with the API exposed in data-inttrie it isn't posssible to implement fromList/toList in time O(n), only O(n log n), assuming that modify/apply are O(log n). Worse yet, if we wanted our fromList to work with infinite lists we would need to do something like import Data.List (genericLength) import Number.Peano.Inf (Nat) -- from peano-inf on Hackage newtype SkipList a = (Nat, IntTrie a) fromList :: [a] -> SkipList a fromList xs = (genericLength xs, fmap (xs !!) identity) The problem here is that 'fromList' is now O(n²). If IntTrie exposed an Traversable interface, I think it would be possible to write a 'fromList' in O(n) using a state monad. However, I don't know if it is possible to write a Traversable interface in the first place. Cheers! =) -- Felipe.

Could you be more specific about what operations you want and their
properties (e.g. performance laziness, etc.)? For example, do you
need to be able to cons onto the front or is the list generated once
and never consed onto? Do you need to be able to insert/remove
elements from the middle? Do you need the tail sharing property that
regular cons lists have?
Michael D. Adams
On Thu, Aug 19, 2010 at 9:22 PM, Evan Laforge
Is there a data type that's spine lazy like a list, but can be seeked (sought?) efficiently? IntMap and Sequence are spine strict so if you take the head element all the elements are forced even if their contents are not. E.g., 'Sequence.index (Sequence.fromList [0..]) 0' will diverge, but obviously 'head [0..]' won't. I can get what I want from a list of lists where the outer list is is 'iterate (drop n)' on the inner one... this is a kind of skip list, right?
It seems like it should be possible to generalize this to multiple levels with increasing skip amounts, then I can seek relatively efficiently and won't force the spine beyond where I seek. Effectively, this is nested list like [[[a]]], where each level above the bottom is something like 'iterate (drop n) level_below'.
Alternately, it should also be possible to do something fancy like a self-modifying data structure that constructs its index as you force bits of it, but this would require some hairy unsafePerformIO, I think.
Has anyone heard of a data structure like this, either the plain list of lists or the self modifying magic one? Surely efficiently indexing a lazy list is something someone else has thought about?
It looks like Luke Palmer's data-inttrie might be doing this, though it's not clear from the documentation. It looks like it lacks emptiness, so it doesn't apply to finite structures.
lazyarray looks like it might be doing the magic self-modifying thing, though it wants a a static bounds right off the bat, which isn't much help when the whole point is to avoid having to figure out how long the input is. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Aug 21, 2010 at 6:52 PM, Michael D. Adams
Could you be more specific about what operations you want and their properties (e.g. performance laziness, etc.)? For example, do you need to be able to cons onto the front or is the list generated once and never consed onto? Do you need to be able to insert/remove elements from the middle? Do you need the tail sharing property that regular cons lists have?
Good questions. It's just generated in one long iterative process (as a complex but lazy transformation of another long list), and then I want to seek to various points and read sequentially (think about music, seeking to a particular spot and then playing). Sections are then recomputed and spliced in (i.e., if you modify a bit of music in the middle, it recomputes that range of time and splices it in). The laziness is that I don't want to compute too far into the future, and it will be common to recompute the entire tail, but never actually need that tail before it needs to be tossed and recomputed again. Currently, I think I've solved my problem by just using a list of chunks. I already use the chunks as the units of recomputation, and since each one accounts for n seconds, seeking to a particular spot or replacing a chunk out of the middle should be plenty fast with a plain list. If each chunk is 5 sec, 3 hours of music is still only a list of 2160 elements, and '[0..] !! 2160' is basically instant. It looks like I need to get up to around 5120000 or so before I can even notice the delay, in plain old interpreted ghci. Lists are fast!

In that case do you also need fast insert and delete? I think both a
pure functional cons list and a pure functional skip list take O(N) to
insert an element or remove an element at position N (because you have
to re-cons the elements in front of it). Also do suffixes need to
also be lists? (e.g. the suffix of a cons list is always a list, but
getting suffix of an array requires allocating a whole new array.)
On Sat, Aug 21, 2010 at 5:00 PM, Evan Laforge
On Sat, Aug 21, 2010 at 6:52 PM, Michael D. Adams
wrote: Could you be more specific about what operations you want and their properties (e.g. performance laziness, etc.)? For example, do you need to be able to cons onto the front or is the list generated once and never consed onto? Do you need to be able to insert/remove elements from the middle? Do you need the tail sharing property that regular cons lists have?
Good questions. It's just generated in one long iterative process (as a complex but lazy transformation of another long list), and then I want to seek to various points and read sequentially (think about music, seeking to a particular spot and then playing). Sections are then recomputed and spliced in (i.e., if you modify a bit of music in the middle, it recomputes that range of time and splices it in). The laziness is that I don't want to compute too far into the future, and it will be common to recompute the entire tail, but never actually need that tail before it needs to be tossed and recomputed again.
Currently, I think I've solved my problem by just using a list of chunks. I already use the chunks as the units of recomputation, and since each one accounts for n seconds, seeking to a particular spot or replacing a chunk out of the middle should be plenty fast with a plain list. If each chunk is 5 sec, 3 hours of music is still only a list of 2160 elements, and '[0..] !! 2160' is basically instant. It looks like I need to get up to around 5120000 or so before I can even notice the delay, in plain old interpreted ghci. Lists are fast!
participants (5)
-
Evan Laforge
-
Felipe Lessa
-
Ivan Lazar Miljenovic
-
Luke Palmer
-
Michael D. Adams