vector-0.6: Efficient Arrays

Portabilitynon-portable
Stabilityexperimental
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>

Data.Vector

Contents

Description

A library for boxed vectors (that is, polymorphic arrays capable of holding any Haskell value). The vectors come in two flavors:

  • mutable
  • immutable

and support a rich interface of both list-like operations, and bulk array operations.

For unboxed arrays, use the Data.Vector.Unboxed interface.

Synopsis

The pure and mutable array types

data Vector a Source

Boxed vectors, supporting efficient slicing.

Instances

Typeable1 Vector 
Vector Vector a 
Eq a => Eq (Vector a) 
Data a => Data (Vector a) 
Ord a => Ord (Vector a) 
Show a => Show (Vector a) 

data MVector s a Source

Mutable boxed vectors keyed on the monad they live in (IO or ST s).

Constructing vectors

empty :: Vector aSource

O(1). empty builds a vector of size zero.

singleton :: a -> Vector aSource

O(1), Vector with exactly one element

cons :: a -> Vector a -> Vector aSource

O(n), Prepend an element to an array.

snoc :: Vector a -> a -> Vector aSource

O(n), Append an element to an array.

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

O(n), Concatenate two vectors

replicate :: Int -> a -> Vector aSource

O(n). replicate n e yields a vector of length n storing e at each position

generate :: Int -> (Int -> a) -> Vector aSource

O(n), Generate a vector of the given length by applying a (pure) generator function to each index

force :: Vector a -> Vector aSource

O(n), Create a copy of a vector. force is useful when dealing with slices, as the garbage collector may be able to free the original vector if no further references are held.

Operations based on length information

length :: Vector a -> IntSource

O(1). Yield the length of a vector as an Int

null :: Vector a -> BoolSource

O(1). null tests whether the given array is empty.

Accessing individual elements

(!) :: Vector a -> Int -> aSource

O(1). Read the element in the vector at the given index.

head :: Vector a -> aSource

O(1). head returns the first element of the vector

last :: Vector a -> aSource

O(n). last yields the last element of an array.

Accessors in a monad

indexM :: Monad m => Vector a -> Int -> m aSource

Monadic indexing which can be strict in the vector while remaining lazy in the element

headM :: Monad m => Vector a -> m aSource

Monadic head which can be strict in the vector while remaining lazy in the element

lastM :: Monad m => Vector a -> m aSource

Monadic last which can be strict in the vector while remaining lazy in the element

Accessor functions with no bounds checking

unsafeIndex :: Vector a -> Int -> aSource

O(1), Unsafe indexing without bounds checking

By not performing bounds checks, this function may be faster when this function is used in an inner loop)

unsafeHead :: Vector a -> aSource

O(1), Yield the first element of a vector without checking if the vector is empty

By not performing bounds checks, this function may be faster when this function is used in an inner loop)

unsafeLast :: Vector a -> aSource

Yield the last element of a vector without checking if the vector is empty

By not performing bounds checks, this function may be faster when this function is used in an inner loop)

unsafeIndexM :: Monad m => Vector a -> Int -> m aSource

Unsafe monadic indexing without bounds checks

unsafeHeadM :: Monad m => Vector a -> m aSource

Unsafe monadic head (access the first element) without bounds checks

unsafeLastM :: Monad m => Vector a -> m aSource

Unsafe monadic last (access the last element) without bounds checks

Subvectors

init :: Vector a -> Vector aSource

O(1), Yield all but the last element without copying.

tail :: Vector a -> Vector aSource

/O(1), Yield all but the first element (without copying).

take :: Int -> Vector a -> Vector aSource

O(1), Yield the first n elements without copying.

drop :: Int -> Vector a -> Vector aSource

O(1), Yield all but the first n elements without copying.

sliceSource

Arguments

:: Int

starting index

-> Int

length

-> Vector a 
-> Vector a 

O(1), Yield a part of the vector without copying it.

Subvector construction without bounds checks

unsafeSliceSource

Arguments

:: Int

starting index

-> Int

length

-> Vector a 
-> Vector a 

O(1), Unsafely yield a part of the vector without copying it and without performing bounds checks.

unsafeInit :: Vector a -> Vector aSource

O(1), Zero-copying init without bounds checks.

unsafeTail :: Vector a -> Vector aSource

O(1), Zero-copying tail without bounds checks.

unsafeTake :: Int -> Vector a -> Vector aSource

O(1), Zero-copying take without bounds checks.

unsafeDrop :: Int -> Vector a -> Vector aSource

O(1), Zero-copying drop without bounds checks.

Permutations

accum :: (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector aSource

TODO accum

accumulate :: (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector aSource

TODO accumulate

accumulate_ :: (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector aSource

TODO accumulate_

(//) :: Vector a -> [(Int, a)] -> Vector aSource

TODO ()

update :: Vector a -> Vector (Int, a) -> Vector aSource

TODO update

update_ :: Vector a -> Vector Int -> Vector a -> Vector aSource

TODO update_

backpermute :: Vector a -> Vector Int -> Vector aSource

backpermute, courtesy Blelloch. The back-permute is a gather/get operation.

reverse :: Vector a -> Vector aSource

O(n), reverse the elements of the given vector.

unsafeAccum :: (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector aSource

TODO unsafeAccum.

unsafeAccumulate :: (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector aSource

TODO unsafeAccumulate

unsafeAccumulate_ :: (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector aSource

TODO unsafeAccumulate_

unsafeUpd :: Vector a -> [(Int, a)] -> Vector aSource

TODO unsafeUpd

unsafeUpdate :: Vector a -> Vector (Int, a) -> Vector aSource

TODO unsafeUpdate

unsafeUpdate_ :: Vector a -> Vector Int -> Vector a -> Vector aSource

TODO unsafeUpdate_

unsafeBackpermute :: Vector a -> Vector Int -> Vector aSource

TODO unsafeBackpermute

Mapping

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

O(n), Map a function over a vector

imap :: (Int -> a -> b) -> Vector a -> Vector bSource

O(n), Apply a function to every index/value pair yielding a new vector

concatMap :: (a -> Vector b) -> Vector a -> Vector bSource

O(n), generate a vector from each element of the input vector, then join the results.

Zipping and unzipping

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

O(n), Zip two vectors with the given function.

zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector dSource

O(n), Zip three vectors with the given function.

zipWith4 :: (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector eSource

O(n), Zip four vectors with the given function.

zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector fSource

O(n), Zip five vectors with the given function.

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector gSource

O(n), Zip six vectors with the given function.

izipWith :: (Int -> a -> b -> c) -> Vector a -> Vector b -> Vector cSource

O(n), Zip two vectors and their indices with the given function.

izipWith3 :: (Int -> a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector dSource

O(n), Zip three vectors and their indices with the given function.

izipWith4 :: (Int -> a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector eSource

O(n), Zip four vectors and their indices with the given function.

izipWith5 :: (Int -> a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector fSource

O(n), Zip five vectors and their indices with the given function.

izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector gSource

O(n), Zip six vectors and their indices with the given function.

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

Elementwise pairing of array elements.

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

zip together three vectors into a vector of triples

zip4 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d)Source

zip5 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector (a, b, c, d, e)Source

zip6 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector (a, b, c, d, e, f)Source

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

Elementwise unpairing of array elements.

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

unzip4 :: Vector (a, b, c, d) -> (Vector a, Vector b, Vector c, Vector d)Source

unzip5 :: Vector (a, b, c, d, e) -> (Vector a, Vector b, Vector c, Vector d, Vector e)Source

unzip6 :: Vector (a, b, c, d, e, f) -> (Vector a, Vector b, Vector c, Vector d, Vector e, Vector f)Source

Filtering

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

O(n), Remove elements from the vector which do not satisfy the predicate

ifilter :: (Int -> a -> Bool) -> Vector a -> Vector aSource

O(n), Drop elements that do not satisfy the predicate (applied to values and their indices)

takeWhile :: (a -> Bool) -> Vector a -> Vector aSource

O(n), Yield the longest prefix of elements satisfying the predicate.

dropWhile :: (a -> Bool) -> Vector a -> Vector aSource

O(n), Drop the longest prefix of elements that satisfy the predicate.

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

Split the vector in two parts, the first one containing those elements that satisfy the predicate and the second one those that don't. The relative order of the elements is preserved at the cost of a (sometimes) reduced performance compared to unstablePartition.

unstablePartition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)Source

O(n), Split the vector in two parts, the first one containing those elements that satisfy the predicate and the second one those that don't. The order of the elements is not preserved.

span :: (a -> Bool) -> Vector a -> (Vector a, Vector a)Source

O(n), Split the vector into the longest prefix of elements that satisfy the predicate and the rest.

break :: (a -> Bool) -> Vector a -> (Vector a, Vector a)Source

Split the vector into the longest prefix of elements that do not satisfy the predicate and the rest.

Searching

elem :: Eq a => a -> Vector a -> BoolSource

Check whether the vector contains an element

notElem :: Eq a => a -> Vector a -> BoolSource

Inverse of elem

find :: (a -> Bool) -> Vector a -> Maybe aSource

Yield Just the first element matching the predicate or Nothing if no such element exists.

findIndex :: (a -> Bool) -> Vector a -> Maybe IntSource

Yield Just the index of the first element matching the predicate or Nothing if no such element exists.

findIndices :: (a -> Bool) -> Vector a -> Vector IntSource

Yield the indices of elements satisfying the predicate

elemIndex :: Eq a => a -> Vector a -> Maybe IntSource

Yield Just the index of the first occurence of the given element or Nothing if the vector does not contain the element

elemIndices :: Eq a => a -> Vector a -> Vector IntSource

Yield the indices of all occurences of the given element

Folding

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

Left fold

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

Left fold on non-empty vectors

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

Left fold with strict accumulator

foldl1' :: (a -> a -> a) -> Vector a -> aSource

Left fold on non-empty vectors with strict accumulator

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

Right fold

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

Right fold on non-empty vectors

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

Right fold with a strict accumulator

foldr1' :: (a -> a -> a) -> Vector a -> aSource

Right fold on non-empty vectors with strict accumulator

ifoldl :: (a -> Int -> b -> a) -> a -> Vector b -> aSource

Left fold (function applied to each element and its index)

ifoldl' :: (a -> Int -> b -> a) -> a -> Vector b -> aSource

Left fold with strict accumulator (function applied to each element and its index)

ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> bSource

Right fold (function applied to each element and its index)

ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> bSource

Right fold with strict accumulator (function applied to each element and its index)

Specialised folds

all :: (a -> Bool) -> Vector a -> BoolSource

O(n). all p u determines whether all elements in array u satisfy predicate p.

any :: (a -> Bool) -> Vector a -> BoolSource

O(n). any p u determines whether any element in array u satisfies predicate p.

and :: Vector Bool -> BoolSource

O(n). and yields the conjunction of a boolean array.

or :: Vector Bool -> BoolSource

O(n). or yields the disjunction of a boolean array.

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

O(n). sum computes the sum (with (+)) of an array of elements.

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

O(n). sum computes the product (with (*)) of an array of elements.

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

O(n). maximum finds the maximum element in an array of orderable elements.

maximumBy :: (a -> a -> Ordering) -> Vector a -> aSource

O(n). maximumBy finds the maximum element in an array under the given ordering.

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

O(n). minimum finds the minimum element in an array of orderable elements.

minimumBy :: (a -> a -> Ordering) -> Vector a -> aSource

O(n). minimumBy finds the minimum element in an array under the given ordering.

minIndex :: Ord a => Vector a -> IntSource

TODO minIndex

minIndexBy :: (a -> a -> Ordering) -> Vector a -> IntSource

TODO minIndexBy

maxIndex :: Ord a => Vector a -> IntSource

TODO maxIndex

maxIndexBy :: (a -> a -> Ordering) -> Vector a -> IntSource

TODO maxIndexBy

Unfolding

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

The unfoldr function is a `dual' to foldr: while foldr reduces a vector to a summary value, unfoldr builds a list from a seed value. The function takes the element and returns Nothing if it is done generating the vector or returns Just (a,b), in which case, a is a prepended to the vector and b is used as the next element in a recursive call.

A simple use of unfoldr:

 unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
  [10,9,8,7,6,5,4,3,2,1]

unfoldrN :: Int -> (b -> Maybe (a, b)) -> b -> Vector aSource

Unfold at most n elements

Scans

prescanl :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Prefix scan

prescanl' :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Prefix scan with strict accumulator

postscanl :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Suffix scan

postscanl' :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Suffix scan with strict accumulator

scanl :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Haskell-style scan function.

scanl' :: (a -> b -> a) -> a -> Vector b -> Vector aSource

Haskell-style scan with strict accumulator

scanl1 :: (a -> a -> a) -> Vector a -> Vector aSource

Scan over a non-empty Vector

scanl1' :: (a -> a -> a) -> Vector a -> Vector aSource

Scan over a non-empty Vector with a strict accumulator

prescanr :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Prefix right-to-left scan

prescanr' :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Prefix right-to-left scan with strict accumulator

postscanr :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Suffix right-to-left scan

postscanr' :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Suffix right-to-left scan with strict accumulator

scanr :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Haskell-style right-to-left scan

scanr' :: (a -> b -> b) -> b -> Vector a -> Vector bSource

Haskell-style right-to-left scan with strict accumulator

scanr1 :: (a -> a -> a) -> Vector a -> Vector aSource

Right-to-left scan over a non-empty vector

scanr1' :: (a -> a -> a) -> Vector a -> Vector aSource

Right-to-left scan over a non-empty vector with a strict accumulator

Enumeration

enumFromN :: Num a => a -> Int -> Vector aSource

Yield a vector of the given length containing the values x, x+1 etc. This operation is usually more efficient than enumFromTo.

enumFromStepN :: Num a => a -> a -> Int -> Vector aSource

Yield a vector of the given length containing the values x, x+y, x+y+y etc. This operations is usually more efficient than enumFromThenTo.

enumFromTo :: Enum a => a -> a -> Vector aSource

Enumerate values from x to y.

WARNING: This operation can be very inefficient. If at all possible, use enumFromN instead.

enumFromThenTo :: Enum a => a -> a -> a -> Vector aSource

Enumerate values from x to y with a specific step z.

WARNING: This operation can be very inefficient. If at all possible, use enumFromStepN instead.

Conversion to/from lists

toList :: Vector a -> [a]Source

Convert a vector to a list

fromList :: [a] -> Vector aSource

Convert a list to a vector

fromListN :: Int -> [a] -> Vector aSource

Convert the first n elements of a list to a vector

 fromListN n xs = fromList (take n xs)

Monadic operations

replicateM :: Monad m => Int -> m a -> m (Vector a)Source

Perform the monadic action the given number of times and store the results in a vector.

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

Apply the monadic action to all elements of the vector, yielding a vector of results

mapM_ :: Monad m => (a -> m b) -> Vector a -> m ()Source

Apply the monadic action to all elements of a vector and ignore the results

forM :: Monad m => Vector a -> (a -> m b) -> m (Vector b)Source

Apply the monadic action to all elements of the vector, yielding a vector of results

forM_ :: Monad m => Vector a -> (a -> m b) -> m ()Source

Apply the monadic action to all elements of a vector and ignore the results

zipWithM :: Monad m => (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)Source

Zip the two vectors with the monadic action and yield a vector of results

zipWithM_ :: Monad m => (a -> b -> m c) -> Vector a -> Vector b -> m ()Source

Zip the two vectors with the monadic action and ignore the results

filterM :: Monad m => (a -> m Bool) -> Vector a -> m (Vector a)Source

Drop elements that do not satisfy the monadic predicate

foldM :: Monad m => (a -> b -> m a) -> a -> Vector b -> m aSource

Monadic fold

foldM' :: Monad m => (a -> b -> m a) -> a -> Vector b -> m aSource

Monadic fold with strict accumulator

fold1M :: Monad m => (a -> a -> m a) -> Vector a -> m aSource

Monadic fold over non-empty vectors

fold1M' :: Monad m => (a -> a -> m a) -> Vector a -> m aSource

Monad fold over non-empty vectors with strict accumulator

Destructive operations

create :: (forall s. ST s (MVector s a)) -> Vector aSource

Destructively initialise a vector.

modify :: (forall s. MVector s a -> ST s ()) -> Vector a -> Vector aSource

Apply a destructive operation to a vector. The operation is applied to a copy of the vector unless it can be safely performed in place.

copy :: PrimMonad m => MVector (PrimState m) a -> Vector a -> m ()Source

Copy an immutable vector into a mutable one. The two vectors must have the same length.

unsafeCopy :: PrimMonad m => MVector (PrimState m) a -> Vector a -> m ()Source

Copy an immutable vector into a mutable one. The two vectors must have the same length. This is not checked.