extended-containers-0.1.1.0: Heap and Vector container types
Safe HaskellNone
LanguageHaskell2010

Data.AMT

Description

Finite vectors

The Vector a type represents a finite vector (or dynamic array) of elements of type a. A Vector is strict in its spine.

The class instances are based on those for lists.

This module should be imported qualified, to avoid name clashes with the Prelude.

Performance

The worst case running time complexities are given, with n referring the the number of elements in the vector. A Vector is particularly efficient for applications that require a lot of indexing and updates. All logarithms are base 16, which means that O(log n) behaves more like O(1) in practice.

For a similar container with efficient concatenation and splitting, but slower indexing and updates, see Seq from the [containers](https:/hackage.haskell.orgpackage/containers) package.

Warning

The length of a Vector must not exceed maxBound :: Int. Violation of this condition is not detected and if the length limit is exceeded, the behaviour of the vector is undefined.

Implementation

The implementation of Vector uses array mapped tries. For a good explanation, see this blog post.

Synopsis

Documentation

data Vector a Source #

An array mapped trie.

Instances

Instances details
Monad Vector Source # 
Instance details

Defined in Data.AMT

Methods

(>>=) :: Vector a -> (a -> Vector b) -> Vector b #

(>>) :: Vector a -> Vector b -> Vector b #

return :: a -> Vector a #

Functor Vector Source # 
Instance details

Defined in Data.AMT

Methods

fmap :: (a -> b) -> Vector a -> Vector b #

(<$) :: a -> Vector b -> Vector a #

MonadFail Vector Source # 
Instance details

Defined in Data.AMT

Methods

fail :: String -> Vector a #

Applicative Vector Source # 
Instance details

Defined in Data.AMT

Methods

pure :: a -> Vector a #

(<*>) :: Vector (a -> b) -> Vector a -> Vector b #

liftA2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

(*>) :: Vector a -> Vector b -> Vector b #

(<*) :: Vector a -> Vector b -> Vector a #

Foldable Vector Source # 
Instance details

Defined in Data.AMT

Methods

fold :: Monoid m => Vector m -> m #

foldMap :: Monoid m => (a -> m) -> Vector a -> m #

foldMap' :: Monoid m => (a -> m) -> Vector a -> m #

foldr :: (a -> b -> b) -> b -> Vector a -> b #

foldr' :: (a -> b -> b) -> b -> Vector a -> b #

foldl :: (b -> a -> b) -> b -> Vector a -> b #

foldl' :: (b -> a -> b) -> b -> Vector a -> b #

foldr1 :: (a -> a -> a) -> Vector a -> a #

foldl1 :: (a -> a -> a) -> Vector a -> a #

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

elem :: Eq a => a -> Vector a -> Bool #

maximum :: Ord a => Vector a -> a #

minimum :: Ord a => Vector a -> a #

sum :: Num a => Vector a -> a #

product :: Num a => Vector a -> a #

Traversable Vector Source # 
Instance details

Defined in Data.AMT

Methods

traverse :: Applicative f => (a -> f b) -> Vector a -> f (Vector b) #

sequenceA :: Applicative f => Vector (f a) -> f (Vector a) #

mapM :: Monad m => (a -> m b) -> Vector a -> m (Vector b) #

sequence :: Monad m => Vector (m a) -> m (Vector a) #

Eq1 Vector Source # 
Instance details

Defined in Data.AMT

Methods

liftEq :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool #

Ord1 Vector Source # 
Instance details

Defined in Data.AMT

Methods

liftCompare :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering #

Read1 Vector Source # 
Instance details

Defined in Data.AMT

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Vector a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Vector a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Vector a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Vector a] #

Show1 Vector Source # 
Instance details

Defined in Data.AMT

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Vector a] -> ShowS #

MonadZip Vector Source # 
Instance details

Defined in Data.AMT

Methods

mzip :: Vector a -> Vector b -> Vector (a, b) #

mzipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

munzip :: Vector (a, b) -> (Vector a, Vector b) #

Alternative Vector Source # 
Instance details

Defined in Data.AMT

Methods

empty :: Vector a #

(<|>) :: Vector a -> Vector a -> Vector a #

some :: Vector a -> Vector [a] #

many :: Vector a -> Vector [a] #

MonadPlus Vector Source # 
Instance details

Defined in Data.AMT

Methods

mzero :: Vector a #

mplus :: Vector a -> Vector a -> Vector a #

IsList (Vector a) Source # 
Instance details

Defined in Data.AMT

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Eq a => Eq (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

(==) :: Vector a -> Vector a -> Bool #

(/=) :: Vector a -> Vector a -> Bool #

Ord a => Ord (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

compare :: Vector a -> Vector a -> Ordering #

(<) :: Vector a -> Vector a -> Bool #

(<=) :: Vector a -> Vector a -> Bool #

(>) :: Vector a -> Vector a -> Bool #

(>=) :: Vector a -> Vector a -> Bool #

max :: Vector a -> Vector a -> Vector a #

min :: Vector a -> Vector a -> Vector a #

Read a => Read (Vector a) Source # 
Instance details

Defined in Data.AMT

Show a => Show (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

a ~ Char => IsString (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

fromString :: String -> Vector a #

Semigroup (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

(<>) :: Vector a -> Vector a -> Vector a #

sconcat :: NonEmpty (Vector a) -> Vector a #

stimes :: Integral b => b -> Vector a -> Vector a #

Monoid (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

NFData a => NFData (Vector a) Source # 
Instance details

Defined in Data.AMT

Methods

rnf :: Vector a -> () #

type Item (Vector a) Source # 
Instance details

Defined in Data.AMT

type Item (Vector a) = a

Construction

empty :: Vector a Source #

O(1). The empty vector.

empty = fromList []

singleton :: a -> Vector a Source #

O(1). A vector with a single element.

singleton x = fromList [x]

fromList :: [a] -> Vector a Source #

O(n * log n). Create a new vector from a list.

fromFunction :: Int -> (Int -> a) -> Vector a Source #

Create a new vector of the given length from a function.

replicate :: Int -> a -> Vector a Source #

O(n * log n). replicate n x is a vector consisting of n copies of x.

replicateA :: Applicative f => Int -> f a -> f (Vector a) Source #

replicateA is an Applicative version of replicate.

unfoldr :: (b -> Maybe (a, b)) -> b -> Vector a Source #

O(n * log n). Build a vector from left to right by repeatedly applying a function to a seed value.

unfoldl :: (b -> Maybe (b, a)) -> b -> Vector a Source #

O(n * log n). Build a vector from right to left by repeatedly applying a function to a seed value.

iterateN :: Int -> (a -> a) -> a -> Vector a Source #

Constructs a vector by repeatedly applying a function to a seed value.

(<|) :: a -> Vector a -> Vector a infixr 5 Source #

O(n * log n). Add an element to the left end of the vector.

(|>) :: Vector a -> a -> Vector a infixl 5 Source #

O(log n). Add an element to the right end of the vector.

(><) :: Vector a -> Vector a -> Vector a infixr 5 Source #

O(m * log n). Concatenate two vectors.

Deconstruction/Subranges

viewl :: Vector a -> Maybe (a, Vector a) Source #

O(n * log n). The first element and the vector without the first element or Nothing if the vector is empty.

viewr :: Vector a -> Maybe (Vector a, a) Source #

O(log n). The vector without the last element and the last element or Nothing if the vector is empty.

head :: Vector a -> Maybe a Source #

O(log n). The first element in the vector or Nothing if the vector is empty.

last :: Vector a -> Maybe a Source #

O(1). The last element in the vector or Nothing if the vector is empty.

take :: Int -> Vector a -> Vector a Source #

O(log n). Take the first n elements of the vector or the vector if n is larger than the length of the vector. Returns the empty vector if n is negative.

Indexing

lookup :: Int -> Vector a -> Maybe a Source #

O(log n). The element at the index or Nothing if the index is out of range.

index :: Int -> Vector a -> a Source #

O(log n). The element at the index. Calls error if the index is out of range.

(!?) :: Vector a -> Int -> Maybe a Source #

O(log n). Flipped version of lookup.

(!) :: Vector a -> Int -> a Source #

O(log n). Flipped version of index.

update :: Int -> a -> Vector a -> Vector a Source #

O(log n). Update the element at the index with a new element. Returns the original vector if the index is out of range.

adjust :: Int -> (a -> a) -> Vector a -> Vector a Source #

O(log n). Adjust the element at the index by applying the function to it. Returns the original vector if the index is out of range.

Transformations

map :: (a -> b) -> Vector a -> Vector b Source #

O(n). Map a function over the vector.

mapWithIndex :: (Int -> a -> b) -> Vector a -> Vector b Source #

O(n). Map a function that has access to the index of an element over the vector.

traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Vector a -> f (Vector b) Source #

O(n). Traverse the vector with a function that has access to the index of an element.

indexed :: Vector a -> Vector (Int, a) Source #

O(n). Pair each element in the vector with its index.

Folds

foldMapWithIndex :: Monoid m => (Int -> a -> m) -> Vector a -> m Source #

O(n). Fold the values in the vector, using the given monoid.

foldlWithIndex :: (b -> Int -> a -> b) -> b -> Vector a -> b Source #

O(n). Fold using the given left-associative function that has access to the index of an element.

foldrWithIndex :: (Int -> a -> b -> b) -> b -> Vector a -> b Source #

O(n). Fold using the given right-associative function that has access to the index of an element.

foldlWithIndex' :: (b -> Int -> a -> b) -> b -> Vector a -> b Source #

O(n). A strict version of foldlWithIndex. Each application of the function is evaluated before using the result in the next application.

foldrWithIndex' :: (Int -> a -> b -> b) -> b -> Vector a -> b Source #

O(n). A strict version of foldrWithIndex. Each application of the function is evaluated before using the result in the next application.

Zipping/Unzipping

zip :: Vector a -> Vector b -> Vector (a, b) Source #

O(n). Takes two vectors and returns a vector of corresponding pairs.

zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

O(n). A generalized zip zipping with a function.

zip3 :: Vector a -> Vector b -> Vector c -> Vector (a, b, c) Source #

O(n). Takes three vectors and returns a vector of corresponding triples.

zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

O(n). A generalized zip3 zipping with a function.

unzip :: Vector (a, b) -> (Vector a, Vector b) Source #

O(n). Transforms a vector of pairs into a vector of first components and a vector of second components.

unzip3 :: Vector (a, b, c) -> (Vector a, Vector b, Vector c) Source #

O(n). Takes a vector of triples and returns three vectors, analogous to unzip.

To Lists

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

O(n). Create a list of index-value pairs from the vector.