-- | Simple but efficient lazy sequence type based on a nested data type and polymorphic recursion. -- -- It is like a list, but instead of @O(1)@ cons\/uncons and @O(k)@ lookup, -- we have amortized @O(1)@ cons/uncons and @O(log(k))@ lookup (both are @O(log(n))@ in the worst case). -- This is somewhat similar to a finger tree (which is also represented by a nested data type), but -- much simpler and more memory efficient (memory usage is basically the same as with lists: amortized -- 3 words per element, plus the data itself). -- -- However, modifying the right end of the sequence is still slow: @O(n)@. This affects the functions -- 'snoc', 'unSnoc', 'append', 'take', 'init'. Somewhat surprisingly, /extracting/ the last element is -- still fast. -- -- An example usage is a pure random-access stack. -- -- This module is intended to be imported qualified. -- {-# LANGUAGE CPP, BangPatterns, PatternSynonyms, PatternGuards #-} module Data.Nested.Seq.Lazy #include "exp_imp.inc" -------------------------------------------------------------------------------- -- | The lazy sequence type. -- -- The underlying (nested) data structure corresponds to the binary representation of the length of the list. It looks like this: -- -- > data Seq a -- > = Nil -- > | Even (Seq (a,a)) -- > | Odd a (Seq (a,a)) -- -- Furthermore we maintain the invariant that @Even Nil@ never appears. -- -- For example, here are how sequences of lengths 4, 5, 6 and 7 are represented: -- -- <> <> <> <> -- data Seq a = Nil -- ^ empty sequence | ZZ (Seq (a,a)) -- ^ even sequence (we will use a pattern synonym to maintain an invariant, hence the strange name) | O a (Seq (a,a)) -- ^ odd sequence #ifdef TESTING deriving Show #endif type Pair a = (a,a) pattern Pair x y = (x,y) -------------------------------------------------------------------------------- #include "sequence.inc" --------------------------------------------------------------------------------