random-access-list-0.2: Random-access lists in Haskell

Data.RandomAccessList

Contents

Description

A random-access list implementation based on Chris Okasaki's approach on his book "Purely Functional Data Structures", Cambridge University Press, 1998, chapter 9.3.

RandomAccessLists are finite lists providing random-access (lookup, update, etc.) in O(log n) while the list functionality head, tail and cons still works in O(1).

A RandomAccessList uses Ints for effective indexing. The valid index range of a RandomAccessList of size n is [0 .. n-1]. If an index is out of range, an error is raised.

Synopsis

The RandomAccessList type

data RandomAccessList a Source

Random-access lists allowing O(1) list operations and O(log n) indexed access.

data View a Source

View the end of a RandomAccessList which is either empty or has been constructed by head and tail.

Constructors

Empty

An empty RandomAccessList.

Cons a (RandomAccessList a)

head and tail of a non-empty RandomAccessList.

Instances

Functor View 
Foldable View 
Eq a => Eq (View a) 
Ord a => Ord (View a) 
Read a => Read (View a) 
Show a => Show (View a) 

Construction

empty :: RandomAccessList aSource

O(1). Builds an empty RandomAccessList.

singleton :: a -> RandomAccessList aSource

O(1). Builds a singleton RandomAccessList.

replicate :: Int -> a -> RandomAccessList aSource

O(n). replicate n x constructs a RandomAccessList that contains the same element x n times.

Query

null :: RandomAccessList a -> BoolSource

O(1). Is the RandomAccessList empty?

length :: RandomAccessList a -> IntSource

O(1). The number of elements contained in a RandomAccessList.

size :: RandomAccessList a -> IntSource

O(1). The number of elements contained in a RandomAccessList.

member :: Eq a => a -> RandomAccessList a -> BoolSource

O(n). Is the given element a member of the RandomAccessList?

index :: Eq a => a -> RandomAccessList a -> Maybe IntSource

O(n). Find the index of a given element.

List specific operations

head :: RandomAccessList a -> aSource

O(1). Returns the head of a RandomAccessList.

tail :: RandomAccessList a -> RandomAccessList aSource

O(1). Retrieve the tail of a RandomAccessList.

uncons :: RandomAccessList a -> (a, RandomAccessList a)Source

O(1). Retrieve both, head and tail of a RandomAccessList.

view :: RandomAccessList a -> View aSource

O(1). Examine a RandomAccessList: Either it is Empty or it has a head and a tail (packed in Cons).

cons :: a -> RandomAccessList a -> RandomAccessList aSource

O(1). Prepend an element to the RandomAccessList.

append :: RandomAccessList a -> RandomAccessList a -> RandomAccessList aSource

O(n) where n is the length of the first list. Appends the second list to the first list.

Random-access specific operations

lookup :: Int -> RandomAccessList a -> aSource

O(log n). Retrieve the ith element of the list. Unless 0 <= i < n, an error is raised.

update :: Int -> a -> RandomAccessList a -> RandomAccessList aSource

O(log n). Set the ith element of the list. Unless 0 <= i < n, an error is raised.

adjust :: (a -> a) -> Int -> RandomAccessList a -> RandomAccessList aSource

O(log n). Adjust ith element of the list according to the given function. Unless 0 <= i < n, an error is raised.

adjustLookupSource

Arguments

:: (a -> a)

Modifying element function.

-> Int

Index of the affected element.

-> RandomAccessList a

RandomAccessList to be modified.

-> (a, RandomAccessList a)

Original element and modified RandomAccessList.

O(log n). Find the ith element of the list and change it. This function returns the element that is at index i in the original RandomAccessList and a new RandomAccessList with the ith element replaced according to the given function:

    lookup   index list === fst (adjustLookup undefined index list)
    adjust f index list === snd (adjustLookup f         index list)

Unless 0 <= i < n, an error is raised.

Miscellaneous

filter :: (a -> Bool) -> RandomAccessList a -> RandomAccessList aSource

O(n). Remove all elements from a RandomAccessList not fulfilling a predicate.

partition :: (a -> Bool) -> RandomAccessList a -> (RandomAccessList a, RandomAccessList a)Source

O(n). Split a RandomAccessList into two: The elements in the first fulfill the given prefix, the others don't.

zip :: RandomAccessList a -> RandomAccessList b -> RandomAccessList (a, b)Source

O(min(n, m)). List-like zip. This function is slightly faster when called with two RandomAccessLists of equal length.

zipWith :: (a -> b -> c) -> RandomAccessList a -> RandomAccessList b -> RandomAccessList cSource

O(min(n, m)). List-like zipWith. This function is slightly faster when called with two RandomAccessLists of equal length.

unzip :: RandomAccessList (a, b) -> (RandomAccessList a, RandomAccessList b)Source

O(n). List-like Prelude.unzip for RandomAccessLists.

Conversion

List

fromList :: [a] -> RandomAccessList aSource

O(n). Build a RandomAccessList from a list.

toList :: RandomAccessList a -> [a]Source

O(n). Convert a RandomAccessList to a list.

toIndexedList :: RandomAccessList a -> [(Int, a)]Source

O(n). Convert a RandomAccessList to a list of tuples each holding an element and its index. The list is ordered ascending regarding the indices.

Map

toMap :: RandomAccessList a -> Map Int aSource

O(n). Build a Map from a RandomAccessList. The keys in the Map are the indices of the elements in the RandomAccessList.

toIntMap :: RandomAccessList a -> IntMap aSource

O(n). Build an IntMap from a RandomAccessList. The keys in the IntMap are the indices of the elements in the RandomAccessList.

Array

fromArray :: (IArray a e, Ix i) => a i e -> RandomAccessList eSource

O(n). Given an IArray, generate a RandomAccessList. The elements' order will be preserved.

toArray :: IArray a e => RandomAccessList e -> a Int eSource

O(n). Build an IArray from the RandomAccessList. It will have an index range from [0 .. n-1], where n is the RandomAccessLists length.