vector-0.5: Efficient Arrays

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

Data.Vector.Generic

Contents

Description

Generic interface to pure vectors

Synopsis

Immutable vectors

class MVector (Mutable v) a => Vector v a whereSource

Class of immutable vectors.

Methods

unsafeFreeze :: PrimMonad m => Mutable v (PrimState m) a -> m (v a)Source

Unsafely convert a mutable vector to its immutable version without copying. The mutable vector may not be used after this operation.

basicLength :: v a -> IntSource

Length of the vector (not fusible!)

basicUnsafeSlice :: Int -> Int -> v a -> v aSource

Yield a part of the vector without copying it. No range checks!

basicUnsafeIndexM :: Monad m => v a -> Int -> m aSource

Yield the element at the given position in a monad. The monad allows us to be strict in the vector if we want. Suppose we had

 unsafeIndex :: v a -> Int -> a

instead. Now, if we wanted to copy a vector, we'd do something like

 copy mv v ... = ... unsafeWrite mv i (unsafeIndex v i) ...

For lazy vectors, the indexing would not be evaluated which means that we would retain a reference to the original vector in each element we write. This is not what we want!

With basicUnsafeIndexM, we can do

 copy mv v ... = ... case basicUnsafeIndexM v i of
                       Box x -> unsafeWrite mv i x ...

which does not have this problem because indexing (but not the returned element!) is evaluated immediately.

elemseq :: v a -> a -> b -> bSource

type family Mutable v :: * -> * -> *Source

Length information

length :: Vector v a => v a -> IntSource

null :: Vector v a => v a -> BoolSource

Construction

empty :: Vector v a => v aSource

Empty vector

singleton :: forall v a. Vector v a => a -> v aSource

Vector with exaclty one element

cons :: forall v a. Vector v a => a -> v a -> v aSource

Prepend an element

snoc :: forall v a. Vector v a => v a -> a -> v aSource

Append an element

replicate :: forall v a. Vector v a => Int -> a -> v aSource

Vector of the given length with the given value in each position

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

Generate a vector of the given length by applying the function to each index

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

Concatenate two vectors

copy :: Vector v a => v a -> v aSource

Create a copy of a vector. Useful when dealing with slices.

Accessing individual elements

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

Indexing

head :: Vector v a => v a -> aSource

First element

last :: Vector v a => v a -> aSource

Last element

indexM :: (Vector v a, Monad m) => v a -> Int -> m aSource

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

headM :: (Vector v a, Monad m) => v a -> m aSource

lastM :: (Vector v a, Monad m) => v a -> m aSource

unsafeIndex :: Vector v a => v a -> Int -> aSource

Unsafe indexing without bounds checking

unsafeHead :: Vector v a => v a -> aSource

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

unsafeLast :: Vector v a => v a -> aSource

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

unsafeIndexM :: (Vector v a, Monad m) => v a -> Int -> m aSource

Unsafe monadic indexing without bounds checks

unsafeHeadM :: (Vector v a, Monad m) => v a -> m aSource

unsafeLastM :: (Vector v a, Monad m) => v a -> m aSource

Subvectors

sliceSource

Arguments

:: Vector v a 
=> Int

starting index

-> Int

length

-> v a 
-> v a 

Yield a part of the vector without copying it.

init :: Vector v a => v a -> v aSource

Yield all but the last element without copying.

tail :: Vector v a => v a -> v aSource

All but the first element (without copying).

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

Yield the first n elements without copying.

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

Yield all but the first n elements without copying.

unsafeSliceSource

Arguments

:: Vector v a 
=> Int

starting index

-> Int

length

-> v a 
-> v a 

Unsafely yield a part of the vector without copying it and without performing bounds checks.

unsafeInit :: Vector v a => v a -> v aSource

unsafeTail :: Vector v a => v a -> v aSource

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

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

Permutations

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

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

accumulate_ :: (Vector v a, Vector v Int, Vector v b) => (a -> b -> a) -> v a -> v Int -> v b -> v aSource

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

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

update_ :: (Vector v a, Vector v Int) => v a -> v Int -> v a -> v aSource

backpermute :: (Vector v a, Vector v Int) => v a -> v Int -> v aSource

reverse :: Vector v a => v a -> v aSource

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

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

unsafeAccumulate_ :: (Vector v a, Vector v Int, Vector v b) => (a -> b -> a) -> v a -> v Int -> v b -> v aSource

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

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

unsafeUpdate_ :: (Vector v a, Vector v Int) => v a -> v Int -> v a -> v aSource

unsafeBackpermute :: (Vector v a, Vector v Int) => v a -> v Int -> v aSource

Mapping

map :: (Vector v a, Vector v b) => (a -> b) -> v a -> v bSource

Map a function over a vector

imap :: (Vector v a, Vector v b) => (Int -> a -> b) -> v a -> v bSource

Apply a function to every index/value pair

concatMap :: (Vector v a, Vector v b) => (a -> v b) -> v a -> v bSource

Zipping and unzipping

zipWith :: (Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> v a -> v b -> v cSource

Zip two vectors with the given function.

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

Zip three vectors with the given function.

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

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

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

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

Zip two vectors and their indices with the given function.

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

Zip three vectors and their indices with the given function.

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

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

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

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

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

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

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

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

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

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

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

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

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

Comparisons

eq :: (Vector v a, Eq a) => v a -> v a -> BoolSource

cmp :: (Vector v a, Ord a) => v a -> v a -> OrderingSource

Filtering

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

Drop elements that do not satisfy the predicate

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

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

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

Yield the longest prefix of elements satisfying the predicate.

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

Drop the longest prefix of elements that satisfy the predicate.

partition :: Vector v a => (a -> Bool) -> v a -> (v a, v 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 :: Vector v a => (a -> Bool) -> v a -> (v a, v 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 order of the elements is not preserved but the operation is often faster than partition.

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

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

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

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

Searching

elem :: (Vector v a, Eq a) => a -> v a -> BoolSource

Check whether the vector contains an element

notElem :: (Vector v a, Eq a) => a -> v a -> BoolSource

Inverse of elem

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

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

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

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

findIndices :: (Vector v a, Vector v Int) => (a -> Bool) -> v a -> v IntSource

Yield the indices of elements satisfying the predicate

elemIndex :: (Vector v a, Eq a) => a -> v 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 :: (Vector v a, Vector v Int, Eq a) => a -> v a -> v IntSource

Yield the indices of all occurences of the given element

Folding

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

Left fold

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

Left fold on non-empty vectors

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

Left fold with strict accumulator

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

Left fold on non-empty vectors with strict accumulator

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

Right fold

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

Right fold on non-empty vectors

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

Right fold with a strict accumulator

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

Right fold on non-empty vectors with strict accumulator

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

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

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

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

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

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

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

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

Specialised folds

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

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

sum :: (Vector v a, Num a) => v a -> aSource

product :: (Vector v a, Num a) => v a -> aSource

maximum :: (Vector v a, Ord a) => v a -> aSource

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

minimum :: (Vector v a, Ord a) => v a -> aSource

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

minIndex :: (Vector v a, Ord a) => v a -> IntSource

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

maxIndex :: (Vector v a, Ord a) => v a -> IntSource

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

Unfolding

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

Scans

prescanl :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Prefix scan

prescanl' :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Prefix scan with strict accumulator

postscanl :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Suffix scan

postscanl' :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Suffix scan with strict accumulator

scanl :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Haskell-style scan

scanl' :: (Vector v a, Vector v b) => (a -> b -> a) -> a -> v b -> v aSource

Haskell-style scan with strict accumulator

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

Scan over a non-empty vector

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

Scan over a non-empty vector with a strict accumulator

prescanr :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

Prefix right-to-left scan

prescanr' :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

Prefix right-to-left scan with strict accumulator

postscanr :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

Suffix right-to-left scan

postscanr' :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

Suffix right-to-left scan with strict accumulator

scanr :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

Haskell-style right-to-left scan

scanr' :: (Vector v a, Vector v b) => (a -> b -> b) -> b -> v a -> v bSource

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

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

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

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

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

Enumeration

enumFromN :: (Vector v a, Num a) => a -> Int -> v aSource

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

enumFromStepN :: forall v a. (Vector v a, Num a) => a -> a -> Int -> v 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 :: (Vector v a, Enum a) => a -> a -> v aSource

Enumerate values from x to y.

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

enumFromThenTo :: (Vector v a, Enum a) => a -> a -> a -> v 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 v a => v a -> [a]Source

Convert a vector to a list

fromList :: Vector v a => [a] -> v aSource

Convert a list to a vector

Conversion to/from Streams

stream :: Vector v a => v a -> Stream aSource

Convert a vector to a Stream

unstream :: Vector v a => Stream a -> v aSource

Create a vector from a Stream

streamR :: Vector v a => v a -> Stream aSource

Convert a vector to a Stream

unstreamR :: Vector v a => Stream a -> v aSource

Create a vector from a Stream

MVector-based initialisation

new :: Vector v a => New a -> v aSource

Construct a pure vector from a monadic initialiser