nested-sequence-0.1: A list-like data structure with O(log(n)) random access

Safe HaskellSafe
LanguageHaskell98

Data.Nested.Seq.Lazy

Contents

Description

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.

Synopsis

Documentation

data Seq a Source

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:

Instances

Functor Seq 
Foldable Seq 
Eq a => Eq (Seq a) 
Ord a => Ord (Seq a) 
Show a => Show (Seq a) 
Monoid (Seq a) 

Accessing the left end of the sequence

cons :: a -> Seq a -> Seq a Source

Prepending an element. Worst case O(log(n)), but amortized O(1).

unCons :: Seq a -> Maybe (a, Seq a) Source

Worst case O(log(n)), amortized O(1)

Basic queries

null :: Seq a -> Bool Source

Checks whether the sequence is empty. This is O(1).

length :: Seq a -> Int Source

The length of a sequence. O(log(n)).

Basic construction

empty :: Seq a Source

The empty sequence.

toList :: Seq a -> [a] Source

Conversion to a list. O(n).

fromList :: [a] -> Seq a Source

Conversion from a list. O(n).

Short sequences

singleton :: a -> Seq a Source

pair :: a -> a -> Seq a Source

triple :: a -> a -> a -> Seq a Source

quad :: a -> a -> a -> a -> Seq a Source

Unsafe head and tail

head :: Seq a -> a Source

First element of the sequence. Worst case O(log(n)), amortized O(1).

tail :: Seq a -> Seq a Source

Tail of the sequence. Worst case O(log(n)), amortized O(1).

last :: Seq a -> a Source

Last element of the sequence. O(log(n)).

Safe head and tail

mbHead :: Seq a -> Maybe a Source

First element of the sequence. Worst case O(log(n)), amortized O(1).

mbTail :: Seq a -> Maybe (Seq a) Source

Tail of the sequence. Worst case O(log(n)), amortized O(1).

tails :: Seq a -> [Seq a] Source

All tails of the sequence (starting with the sequence itself)

mbLast :: Seq a -> Maybe a Source

Last element of the sequence. O(log(n))

Indexing

lookup :: Int -> Seq a -> a Source

Lookup the k-th element of a sequence. This is worst case O(log(n)) and amortized O(log(k)), and quite efficient.

mbLookup :: Int -> Seq a -> Maybe a Source

update :: (a -> a) -> Int -> Seq a -> Seq a Source

Update the k-th element of a sequence.

replace :: Int -> a -> Seq a -> Seq a Source

Replace the k-th element. replace n x == update (const x) n

drop :: Int -> Seq a -> Seq a Source

Drop is efficient: drop k is amortized O(log(k)), worst case maybe O(log(n)^2) ?

Slow operations

append :: Seq a -> Seq a -> Seq a Source

O(n) (for large n at least), where n is the length of the first sequence.

take :: Int -> Seq a -> Seq a Source

Take is slow: O(n)

init :: Seq a -> Seq a Source

The sequence without the last element. Warning, this is slow, O(n)

mbInit :: Seq a -> Maybe (Seq a) Source

The sequence without the last element. Warning, this is slow, O(n)

snoc :: Seq a -> a -> Seq a Source

Warning, this is slow: O(n) (with bad constant factor).

unSnoc :: Seq a -> Maybe (Seq a, a) Source

Stripping the last element from a sequence is a slow operation, O(n). If you only need extracting the last element, use mbLast instead, which is fast.

Debugging

toListNaive :: Seq a -> [a] Source

Naive implementation of toList

checkInvariant :: Seq a -> Bool Source

We maintain the invariant that (Z Nil) never appears. This function checks whether this is satisfied. Used only for testing.

showInternal :: Show a => Seq a -> String Source

Show the internal structure of the sequence. The constructor names Z and O come from "zero" and "one", respectively.

graphviz :: Show a => Seq a -> String Source

Generates a graphviz DOT file, showing the internal structure of a sequence