vector-0.4.2: 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 Vector v a whereSource

Class of immutable vectors.

Methods

vnew :: (forall mv m. MVector mv m a => m (mv a)) -> v aSource

Construct a pure vector from a monadic initialiser (not fusible!)

vlength :: v a -> IntSource

Length of the vector (not fusible!)

unsafeSlice :: v a -> Int -> Int -> v aSource

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

unsafeIndexM :: 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 unsafeIndexM, we can do

 copy mv v ... = ... case unsafeIndexM 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.

Instances

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 :: Vector v a => a -> v aSource

Vector with exaclty one element

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

Prepend an element

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

Append an element

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

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

(++) :: 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

Subvectors

sliceSource

Arguments

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

starting index

-> Int

length

-> v a 

Yield a part of the vector without copying it. Safer version of unsafeSlice.

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.

Permutations

accum :: Vector v a => (a -> b -> a) -> v a -> [(Int, 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

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

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

Mapping

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

Map a function over a vector

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.

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

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

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 which do not satisfy the predicate

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.

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.

Folding

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

Left fold

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

Lefgt 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

Specialised folds

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

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

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

Enumeration

enumFromTo :: (Vector v a, Enum a) => a -> a -> v aSource

enumFromThenTo :: (Vector v a, Enum a) => a -> a -> a -> v aSource

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

MVector-based initialisation

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

Construct a pure vector from a monadic initialiser