vector-functorlazy-0.0.1: vectors that perform the fmap operation in constant time

Safe HaskellNone

Data.Vector.FunctorLazy

Contents

Description

Functor-lazy vectors are like boxed vectors, but support mapping a function onto all elements in constant time. All vector operations (except slicing) are fully supported. See http://github.com/mikeizbicki/functor-lazy for more details.

Synopsis

Functor-lazy vectors

data Vector a Source

Instances

data MVector s a Source

Instances

Accessors

Length information

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

O(1) Yield the length of the vector.

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

O(1) Test whether a vector if empty

Indexing

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

O(1) Indexing

(!?) :: Vector v a => v a -> Int -> Maybe a

O(1) Safe indexing

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

O(1) First element

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

O(1) Last element

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

O(1) Unsafe indexing without bounds checking

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

O(1) First element without checking if the vector is empty

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

O(1) Last element without checking if the vector is empty

Monadic indexing

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

O(1) Indexing in a monad.

The monad allows operations to be strict in the vector when necessary. Suppose vector copying is implemented like this:

 copy mv v = ... write mv i (v ! i) ...

For lazy vectors, v ! i would not be evaluated which means that mv would unnecessarily retain a reference to v in each element written.

With indexM, copying can be implemented like this instead:

 copy mv v = ... do
                   x <- indexM v i
                   write mv i x

Here, no references to v are retained because indexing (but not the elements) is evaluated eagerly.

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

O(1) First element of a vector in a monad. See indexM for an explanation of why this is useful.

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

O(1) Last element of a vector in a monad. See indexM for an explanation of why this is useful.

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

O(1) Indexing in a monad without bounds checks. See indexM for an explanation of why this is useful.

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

O(1) First element in a monad without checking for empty vectors. See indexM for an explanation of why this is useful.

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

O(1) Last element in a monad without checking for empty vectors. See indexM for an explanation of why this is useful.

Construction

Initialisation

empty :: Vector v a => v a

O(1) Empty vector

singleton :: Vector v a => a -> v a

O(1) Vector with exactly one element

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

O(n) Vector of the given length with the same value in each position

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

O(n) Construct a vector of the given length by applying the function to each index

iterateN :: Vector v a => Int -> (a -> a) -> a -> v a

O(n) Apply function n times to value. Zeroth element is original value.

Monadic initialisation

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

O(n) Execute the monadic action the given number of times and store the results in a vector.

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

O(n) Construct a vector of the given length by applying the monadic action to each index

create :: Vector v a => (forall s. ST s (Mutable v s a)) -> v a

Execute the monadic action and freeze the resulting vector.

 create (do { v <- new 2; write v 0 'a'; write v 1 'b'; return v }) = <a,b>

Unfolding

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

O(n) Construct a vector by repeatedly applying the generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

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

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

O(n) Construct a vector with at most n by repeatedly applying the generator function to the a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

 unfoldrN 3 (\n -> Just (n,n-1)) 10 = <10,9,8>

constructN :: Vector v a => Int -> (v a -> a) -> v a

O(n) Construct a vector with n elements by repeatedly applying the generator function to the already constructed part of the vector.

 constructN 3 f = let a = f <> ; b = f <a> ; c = f <a,b> in f <a,b,c>

constructrN :: Vector v a => Int -> (v a -> a) -> v a

O(n) Construct a vector with n elements from right to left by repeatedly applying the generator function to the already constructed part of the vector.

 constructrN 3 f = let a = f <> ; b = f<a> ; c = f <b,a> in f <c,b,a>

Enumeration

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

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

 enumFromN 5 3 = <5,6,7>

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

O(n) 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.

 enumFromStepN 1 0.1 5 = <1,1.1,1.2,1.3,1.4>

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

O(n) 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 a

O(n) 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.

Concatenation

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

O(n) Prepend an element

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

O(n) Append an element

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

O(m+n) Concatenate two vectors

concat :: Vector v a => [v a] -> v a

O(n) Concatenate all vectors in the list

Restricting memory usage

force :: Vector v a => v a -> v a

O(n) Yield the argument but force it not to retain any extra memory, possibly by copying it.

This is especially useful when dealing with slices. For example:

 force (slice 0 2 <huge vector>)

Here, the slice retains a reference to the huge vector. Forcing it creates a copy of just the elements that belong to the slice and allows the huge vector to be garbage collected.

Modifying vectors

Bulk updates

(//)

Arguments

:: Vector v a 
=> v a

initial vector (of length m)

-> [(Int, a)]

list of index/value pairs (of length n)

-> v a 

O(m+n) For each pair (i,a) from the list, replace the vector element at position i by a.

 <5,9,2,7> // [(2,1),(0,3),(2,8)] = <3,9,8,7>

update

Arguments

:: (Vector v a, Vector v (Int, a)) 
=> v a

initial vector (of length m)

-> v (Int, a)

vector of index/value pairs (of length n)

-> v a 

O(m+n) For each pair (i,a) from the vector of index/value pairs, replace the vector element at position i by a.

 update <5,9,2,7> <(2,1),(0,3),(2,8)> = <3,9,8,7>

update_

Arguments

:: (Vector v a, Vector v Int) 
=> v a

initial vector (of length m)

-> v Int

index vector (of length n1)

-> v a

value vector (of length n2)

-> v a 

O(m+min(n1,n2)) For each index i from the index vector and the corresponding value a from the value vector, replace the element of the initial vector at position i by a.

 update_ <5,9,2,7>  <2,0,2> <1,3,8> = <3,9,8,7>

This function is useful for instances of Vector that cannot store pairs. Otherwise, update is probably more convenient.

 update_ xs is ys = update xs (zip is ys)

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

Same as (//) but without bounds checking.

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

Same as update but without bounds checking.

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

Same as update_ but without bounds checking.

Accumulations

accum

Arguments

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

accumulating function f

-> v a

initial vector (of length m)

-> [(Int, b)]

list of index/value pairs (of length n)

-> v a 

O(m+n) For each pair (i,b) from the list, replace the vector element a at position i by f a b.

 accum (+) <5,9,2> [(2,4),(1,6),(0,3),(1,7)] = <5+3, 9+6+7, 2+4>

accumulate

Arguments

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

accumulating function f

-> v a

initial vector (of length m)

-> v (Int, b)

vector of index/value pairs (of length n)

-> v a 

O(m+n) For each pair (i,b) from the vector of pairs, replace the vector element a at position i by f a b.

 accumulate (+) <5,9,2> <(2,4),(1,6),(0,3),(1,7)> = <5+3, 9+6+7, 2+4>

accumulate_

Arguments

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

accumulating function f

-> v a

initial vector (of length m)

-> v Int

index vector (of length n1)

-> v b

value vector (of length n2)

-> v a 

O(m+min(n1,n2)) For each index i from the index vector and the corresponding value b from the the value vector, replace the element of the initial vector at position i by f a b.

 accumulate_ (+) <5,9,2> <2,1,0,1> <4,6,3,7> = <5+3, 9+6+7, 2+4>

This function is useful for instances of Vector that cannot store pairs. Otherwise, accumulate is probably more convenient:

 accumulate_ f as is bs = accumulate f as (zip is bs)

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

Same as accum but without bounds checking.

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

Same as accumulate but without bounds checking.

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

Same as accumulate_ but without bounds checking.

Permutations

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

O(n) Reverse a vector

backpermute

Arguments

:: (Vector v a, Vector v Int) 
=> v a

xs value vector

-> v Int

is index vector (of length n)

-> v a 

O(n) Yield the vector obtained by replacing each element i of the index vector by xs!i. This is equivalent to map (xs!) is but is often much more efficient.

 backpermute <a,b,c,d> <0,3,2,3,1,0> = <a,d,c,d,b,a>

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

Same as backpermute but without bounds checking.

Safe destructive updates

modify :: Vector v a => (forall s. Mutable v s a -> ST s ()) -> v a -> v a

Apply a destructive operation to a vector. The operation will be performed in place if it is safe to do so and will modify a copy of the vector otherwise.

 modify (\v -> write v 0 'x') (replicate 3 'a') = <'x','a','a'>

Elementwise operations

Indexing

indexed :: (Vector v a, Vector v (Int, a)) => v a -> v (Int, a)

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

Zipping

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

O(min(m,n)) 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 d

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 e

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 f

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 g

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

O(min(m,n)) Zip two vectors with a function that also takes the elements' indices.

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 d

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 e

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 f

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 g

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

O(min(m,n)) Zip two vectors

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)

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)

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)

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)

Monadic zipping

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

O(min(m,n)) Zip the two vectors with the monadic action and yield a vector of results

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

O(min(m,n)) Zip the two vectors with the monadic action and ignore the results

Unzipping

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

O(min(m,n)) Unzip a vector of pairs.

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)

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)

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)

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)

Working with predicates

Filtering

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

O(n) Drop elements that do not satisfy the predicate

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

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

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

O(n) Drop elements that do not satisfy the monadic predicate

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

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

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

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

Searching

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

O(n) Check if the vector contains an element

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

O(n) Check if the vector does not contain an element (inverse of elem)

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

O(n) Yield Just the first element matching the predicate or Nothing if no such element exists.

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

O(n) 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 Int

O(n) Yield the indices of elements satisfying the predicate in ascending order.

elemIndex :: (Vector v a, Eq a) => a -> v a -> Maybe Int

O(n) Yield Just the index of the first occurence of the given element or Nothing if the vector does not contain the element. This is a specialised version of findIndex.

elemIndices :: (Vector v a, Vector v Int, Eq a) => a -> v a -> v Int

O(n) Yield the indices of all occurences of the given element in ascending order. This is a specialised version of findIndices.

Folding

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

O(n) Left fold

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

O(n) Left fold on non-empty vectors

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

O(n) Left fold with strict accumulator

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

O(n) Left fold on non-empty vectors with strict accumulator

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

O(n) Right fold

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

O(n) Right fold on non-empty vectors

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

O(n) Right fold with a strict accumulator

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

O(n) Right fold on non-empty vectors with strict accumulator

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

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

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

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

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

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

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

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

Specialised folds

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

O(n) Check if all elements satisfy the predicate.

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

O(n) Check if any element satisfies the predicate.

and :: Vector v Bool => v Bool -> Bool

O(n) Check if all elements are True

or :: Vector v Bool => v Bool -> Bool

O(n) Check if any element is True

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

O(n) Compute the sum of the elements

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

O(n) Compute the produce of the elements

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

O(n) Yield the maximum element of the vector. The vector may not be empty.

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

O(n) Yield the maximum element of the vector according to the given comparison function. The vector may not be empty.

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

O(n) Yield the minimum element of the vector. The vector may not be empty.

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

O(n) Yield the minimum element of the vector according to the given comparison function. The vector may not be empty.

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

O(n) Yield the index of the minimum element of the vector. The vector may not be empty.

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

O(n) Yield the index of the minimum element of the vector according to the given comparison function. The vector may not be empty.

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

O(n) Yield the index of the maximum element of the vector. The vector may not be empty.

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

O(n) Yield the index of the maximum element of the vector according to the given comparison function. The vector may not be empty.

Monadic folds

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

O(n) Monadic fold

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

O(n) Monadic fold with strict accumulator

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

O(n) Monadic fold over non-empty vectors

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

O(n) Monadic fold over non-empty vectors with strict accumulator

foldM_ :: (Monad m, Vector v b) => (a -> b -> m a) -> a -> v b -> m ()

O(n) Monadic fold that discards the result

foldM'_ :: (Monad m, Vector v b) => (a -> b -> m a) -> a -> v b -> m ()

O(n) Monadic fold with strict accumulator that discards the result

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

O(n) Monadic fold over non-empty vectors that discards the result

fold1M'_ :: (Monad m, Vector v a) => (a -> a -> m a) -> v a -> m ()

O(n) Monad fold over non-empty vectors with strict accumulator that discards the result

Monadic sequencing

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

Evaluate each action and collect the results

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

Evaluate each action and discard the results

Prefix sums (scans)

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

O(n) Prescan

 prescanl f z = init . scanl f z

Example: prescanl (+) 0 <1,2,3,4> = <0,1,3,6>

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

O(n) Prescan with strict accumulator

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

O(n) Scan

 postscanl f z = tail . scanl f z

Example: postscanl (+) 0 <1,2,3,4> = <1,3,6,10>

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

O(n) Scan with strict accumulator

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

O(n) Haskell-style scan

 scanl f z <x1,...,xn> = <y1,...,y(n+1)>
   where y1 = z
         yi = f y(i-1) x(i-1)

Example: scanl (+) 0 <1,2,3,4> = <0,1,3,6,10>

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

O(n) Haskell-style scan with strict accumulator

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

O(n) Scan over a non-empty vector

 scanl f <x1,...,xn> = <y1,...,yn>
   where y1 = x1
         yi = f y(i-1) xi

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

O(n) Scan over a non-empty vector with a strict accumulator

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

O(n) Right-to-left prescan

 prescanr f z = reverse . prescanl (flip f) z . reverse

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

O(n) Right-to-left prescan with strict accumulator

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

O(n) Right-to-left scan

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

O(n) Right-to-left scan with strict accumulator

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

O(n) Right-to-left Haskell-style scan

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

O(n) Right-to-left Haskell-style scan with strict accumulator

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

O(n) Right-to-left scan over a non-empty vector

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

O(n) Right-to-left scan over a non-empty vector with a strict accumulator

Conversions

Lists

toList :: Vector v a => v a -> [a]

O(n) Convert a vector to a list

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

O(n) Convert a list to a vector

fromListN :: Vector v a => Int -> [a] -> v a

O(n) Convert the first n elements of a list to a vector

 fromListN n xs = fromList (take n xs)

Other vector types

convert :: (Vector v a, Vector w a) => v a -> w a

O(n) Convert different vector types

Mutable vectors

freeze :: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> m (v a)

O(n) Yield an immutable copy of the mutable vector.

thaw :: (PrimMonad m, Vector v a) => v a -> m (Mutable v (PrimState m) a)

O(n) Yield a mutable copy of the immutable vector.

copy :: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> v a -> m ()

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

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

O(1) Unsafe convert a mutable vector to an immutable one without copying. The mutable vector may not be used after this operation.

unsafeThaw :: (PrimMonad m, Vector v a) => v a -> m (Mutable v (PrimState m) a)

O(1) Unsafely convert an immutable vector to a mutable one without copying. The immutable vector may not be used after this operation.

unsafeCopy :: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> v a -> m ()

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