-- | Simple but efficient lazy list-like sequence type based on a nested data 
-- type and polymorphic recursion. Also called \"binary random-access list\"
--
-- 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. Memory usage is basically the same as with lists: on average 
-- 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 stack.
--
-- This module is intended to be imported qualified.
--

{-# LANGUAGE CPP, BangPatterns, PatternSynonyms, PatternGuards #-}
module Data.Nested.Seq.Binary.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.
--
-- If the @Odd@ constructor was missing, this would be a /full binary tree/. Note that the
-- nested data type representation has two advantages compared to a naive binary tree type
-- (by which we mean the usual @data Tree a = Node a a | Leaf a@ construction): 
-- First, the type system guarantees the fullness; second, it has smaller memory footprint, since
-- in the naive case, the @Leaf@ constructors introduce two extra words (a tag word and a pointer).
--
-- With the @Odd@ constructor thrown in, this is a sequence of larger and larger full 
-- binary trees. Looking at the binary representation of the length of the list, we will have full
-- binary trees corresponding to the positions of @1@ digits.
--
-- For example, here are how sequences of lengths 4, 5, 6 and 7 are represented:
--
-- <<doc/seq4.png>> <<doc/seq5.png>> <<doc/seq6.png>> <<doc/seq7.png>>
--
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 :: a -> a -> Pair a
pattern Pair x y = (x,y)

--------------------------------------------------------------------------------

#include "sequence.inc"

--------------------------------------------------------------------------------