joinlist-0.3.0: Join list - symmetric list type

Portabilityto be determined.
Stabilityhighly unstable
MaintainerStephen Tetley <stephen.tetley@gmail.com>

Data.JoinList

Contents

Description

A "join list" datatype and operations.

A join list is implemented a binary tree, so joining two lists (catenation, aka (++)) is a cheap operation.

This constrasts with the regular list datatype which is a cons list: while consing on a regular list is by nature cheap, joining (++) is expensive.

Synopsis

Join list datatype, opaque.

Views as per Data.Sequence

data ViewL a Source

Constructors

EmptyL 
a :< (JoinList a) 

Instances

Functor ViewL 
Eq a => Eq (ViewL a) 
Show a => Show (ViewL a) 

data ViewR a Source

Constructors

EmptyR 
(JoinList a) :> a 

Instances

Functor ViewR 
Eq a => Eq (ViewR a) 
Show a => Show (ViewR a) 

Conversion between join lists and regular lists

fromList :: [a] -> JoinList aSource

Build a join list from a regular list.

toList :: JoinList a -> [a]Source

Convert a join list to a regular list.

Construction

empty :: JoinList aSource

Create an empty join list.

singleton :: a -> JoinList aSource

Create a singleton join list.

cons :: a -> JoinList a -> JoinList aSource

Cons an element to the front of the join list.

snoc :: JoinList a -> a -> JoinList aSource

Snoc an element to the tail of the join list.

(++) :: JoinList a -> JoinList a -> JoinList aSource

Catenate two join lists. Unlike (++) on regular lists, catenation on join lists is (relatively) cheap hence the name join list.

join :: JoinList a -> JoinList a -> JoinList aSource

An alias for (++) that does not cause a name clash with the Prelude.

Basic functions

head :: JoinList a -> aSource

Extract the first element of a join list - i.e. the leftmost element of the left spine. An error is thrown if the list is empty.

This function performs a traversal down the left spine, so unlike head on regular lists this function is not performed in constant time.

last :: JoinList a -> aSource

Extract the last element of a join list - i.e. the rightmost element of the right spine. An error is thrown if the list is empty.

tail :: JoinList a -> JoinList aSource

Extract the elements after the head of a list. An error is thrown if the list is empty.

init :: JoinList a -> JoinList aSource

Extract all the elements except the last one. An error is thrown if the list is empty.

null :: JoinList a -> BoolSource

Test whether a join list is empty.

concat :: JoinList (JoinList a) -> JoinList aSource

Concatenate a join list of join lists.

length :: JoinList a -> IntSource

Get the length of a join list.

map :: (a -> b) -> JoinList a -> JoinList bSource

Map a function over a join list.

Building join lists

replicate :: Int -> a -> JoinList aSource

Build a join list of n elements.

repeated :: Int -> JoinList a -> JoinList aSource

Repeatedly build a join list by catenating the seed list.

Folds and unfolds

gfold :: b -> (a -> b) -> (b -> b -> b) -> JoinList a -> bSource

A generalized fold, where each constructor has an operation.

foldr :: (a -> b -> b) -> b -> JoinList a -> bSource

Right-associative fold of a JoinList.

foldl :: (b -> a -> b) -> b -> JoinList a -> bSource

Left-associative fold of a JoinList.

unfoldl :: (b -> Maybe (a, b)) -> b -> JoinList aSource

unfoldl is permitted due to cheap snoc-ing.

unfoldr :: (b -> Maybe (a, b)) -> b -> JoinList aSource

unfoldr - the usual unfoldr opertation.

Views

viewl :: JoinList a -> ViewL aSource

Access the left end of a sequence.

Unlike the corresponing operation on Data.Sequence this is not a cheap operation, the joinlist must be traversed down the left spine to find the leftmost node.

Also the traversal may involve changing the shape of the underlying binary tree.

viewr :: JoinList a -> ViewR aSource

Access the rightt end of a sequence.

Unlike the corresponing operation on Data.Sequence this is not a cheap operation, the joinlist must be traversed down the right spine to find the rightmost node.

Also the traversal may involve changing the shape of the underlying binary tree.

Sublists

takeLeft :: Int -> JoinList a -> JoinList aSource

Take the left n elements of the list.

Implemented with viewl hence the same performance caveats apply.

takeRight :: Int -> JoinList a -> JoinList aSource

Take the right n elements of the list.

Implemented with viewr hence the same performance caveats apply.

dropLeft :: Int -> JoinList a -> JoinList aSource

Drop the left n elements of the list.

Implemented with viewl hence the same performance caveats apply.

dropRight :: Int -> JoinList a -> JoinList aSource

Drop the right n elements of the list.

Implemented with viewr hence the same performance caveats apply.

Zipping (deprecated)

xzip :: JoinList a -> [b] -> JoinList (a, b)Source

This function should be considered deprecated.

cross zip - zip a join list against a regular list, maintaining the shape of the join list provided the lengths of the lists match.

xzipWith :: (a -> b -> c) -> JoinList a -> [b] -> JoinList cSource

This function should be considered deprecated.

Generalized cross zip - c.f. zipWith on regular lists.