Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module re-exports the functionality in Sized
specialized to Vector
.
Functions returning a vector determine the size from the type context unless
they have a '
suffix in which case they take an explicit Proxy
argument.
Functions where the resultant vector size is not know until compile time are not exported.
- type Vector = Vector Vector
- length :: forall n a. KnownNat n => Vector n a -> Int
- length' :: forall n a. KnownNat n => Vector n a -> Proxy n
- index :: forall n a. KnownNat n => Vector n a -> Int -> a
- index' :: forall n m a. (KnownNat n, KnownNat m) => Vector (n + m) a -> Proxy n -> a
- unsafeIndex :: forall n a. KnownNat n => Vector n a -> Int -> a
- head :: forall n a. Vector (n + 1) a -> a
- last :: forall n a. Vector (n + 1) a -> a
- indexM :: forall n a m. (KnownNat n, Monad m) => Vector n a -> Int -> m a
- indexM' :: forall n k a m. (KnownNat n, KnownNat k, Monad m) => Vector (n + k) a -> Proxy n -> m a
- unsafeIndexM :: forall n a m. (KnownNat n, Monad m) => Vector n a -> Int -> m a
- headM :: forall n a m. (KnownNat n, Monad m) => Vector (n + 1) a -> m a
- lastM :: forall n a m. (KnownNat n, Monad m) => Vector (n + 1) a -> m a
- slice :: forall i n a. (KnownNat i, KnownNat n) => Proxy i -> Vector (i + n) a -> Vector n a
- slice' :: forall i n a. (KnownNat i, KnownNat n) => Proxy i -> Proxy n -> Vector (i + n) a -> Vector n a
- init :: forall n a. Vector (n + 1) a -> Vector n a
- tail :: forall n a. Vector (n + 1) a -> Vector n a
- take :: forall n m a. (KnownNat n, KnownNat m) => Vector (m + n) a -> Vector n a
- take' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (m + n) a -> Vector n a
- drop :: forall n m a. (KnownNat n, KnownNat m) => Vector (m + n) a -> Vector m a
- drop' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (m + n) a -> Vector m a
- splitAt :: forall n m a. (KnownNat n, KnownNat m) => Vector (n + m) a -> (Vector n a, Vector m a)
- splitAt' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (n + m) a -> (Vector n a, Vector m a)
- empty :: forall a. Vector 0 a
- singleton :: forall a. a -> Vector 1 a
- replicate :: forall n a. KnownNat n => a -> Vector n a
- replicate' :: forall n a. KnownNat n => Proxy n -> a -> Vector n a
- generate :: forall n a. KnownNat n => (Int -> a) -> Vector n a
- generate' :: forall n a. KnownNat n => Proxy n -> (Int -> a) -> Vector n a
- iterateN :: forall n a. KnownNat n => (a -> a) -> a -> Vector n a
- iterateN' :: forall n a. KnownNat n => Proxy n -> (a -> a) -> a -> Vector n a
- replicateM :: forall n m a. (KnownNat n, Monad m) => m a -> m (Vector n a)
- replicateM' :: forall n m a. (KnownNat n, Monad m) => Proxy n -> m a -> m (Vector n a)
- generateM :: forall n m a. (KnownNat n, Monad m) => (Int -> m a) -> m (Vector n a)
- generateM' :: forall n m a. (KnownNat n, Monad m) => Proxy n -> (Int -> m a) -> m (Vector n a)
- unfoldrN :: forall n a b. KnownNat n => (b -> (a, b)) -> b -> Vector n a
- unfoldrN' :: forall n a b. KnownNat n => Proxy n -> (b -> (a, b)) -> b -> Vector n a
- enumFromN :: forall n a. (KnownNat n, Num a) => a -> Vector n a
- enumFromN' :: forall n a. (KnownNat n, Num a) => a -> Proxy n -> Vector n a
- enumFromStepN :: forall n a. (KnownNat n, Num a) => a -> a -> Vector n a
- enumFromStepN' :: forall n a. (KnownNat n, Num a) => a -> a -> Proxy n -> Vector n a
- cons :: forall n a. a -> Vector n a -> Vector (n + 1) a
- snoc :: forall n a. Vector n a -> a -> Vector (n + 1) a
- (++) :: forall n m a. Vector n a -> Vector m a -> Vector (n + m) a
- force :: Vector n a -> Vector n a
- (//) :: Vector m a -> [(Int, a)] -> Vector m a
- update :: Vector m a -> Vector n (Int, a) -> Vector m a
- update_ :: Vector m a -> Vector n Int -> Vector n a -> Vector m a
- unsafeUpd :: Vector m a -> [(Int, a)] -> Vector m a
- unsafeUpdate :: Vector m a -> Vector n (Int, a) -> Vector m a
- unsafeUpdate_ :: Vector m a -> Vector n Int -> Vector n a -> Vector m a
- accum :: (a -> b -> a) -> Vector m a -> [(Int, b)] -> Vector m a
- accumulate :: (a -> b -> a) -> Vector m a -> Vector n (Int, b) -> Vector m a
- accumulate_ :: (a -> b -> a) -> Vector m a -> Vector n Int -> Vector n b -> Vector m a
- unsafeAccum :: (a -> b -> a) -> Vector m a -> [(Int, b)] -> Vector m a
- unsafeAccumulate :: (a -> b -> a) -> Vector m a -> Vector n (Int, b) -> Vector m a
- unsafeAccumulate_ :: (a -> b -> a) -> Vector m a -> Vector n Int -> Vector n b -> Vector m a
- reverse :: Vector n a -> Vector n a
- backpermute :: Vector m a -> Vector n Int -> Vector n a
- unsafeBackpermute :: Vector m a -> Vector n Int -> Vector n a
- indexed :: Vector n a -> Vector n (Int, a)
- map :: (a -> b) -> Vector n a -> Vector n b
- imap :: (Int -> a -> b) -> Vector n a -> Vector n b
- concatMap :: (a -> Vector m b) -> Vector n a -> Vector (n * m) b
- mapM :: Monad m => (a -> m b) -> Vector n a -> m (Vector n b)
- imapM :: Monad m => (Int -> a -> m b) -> Vector n a -> m (Vector n b)
- mapM_ :: Monad m => (a -> m b) -> Vector n a -> m ()
- imapM_ :: Monad m => (Int -> a -> m b) -> Vector n a -> m ()
- forM :: Monad m => Vector n a -> (a -> m b) -> m (Vector n b)
- forM_ :: Monad m => Vector n a -> (a -> m b) -> m ()
- zipWith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
- zipWith3 :: (a -> b -> c -> d) -> Vector n a -> Vector n b -> Vector n c -> Vector n d
- zipWith4 :: (a -> b -> c -> d -> e) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n g
- izipWith :: (Int -> a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
- izipWith3 :: (Int -> a -> b -> c -> d) -> Vector n a -> Vector n b -> Vector n c -> Vector n d
- izipWith4 :: (Int -> a -> b -> c -> d -> e) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e
- izipWith5 :: (Int -> a -> b -> c -> d -> e -> f) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f
- izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n g
- zip :: Vector n a -> Vector n b -> Vector n (a, b)
- zip3 :: Vector n a -> Vector n b -> Vector n c -> Vector n (a, b, c)
- zip4 :: Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n (a, b, c, d)
- zip5 :: Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n (a, b, c, d, e)
- zip6 :: Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n (a, b, c, d, e, f)
- zipWithM :: Monad m => (a -> b -> m c) -> Vector n a -> Vector n b -> m (Vector n c)
- izipWithM :: Monad m => (Int -> a -> b -> m c) -> Vector n a -> Vector n b -> m (Vector n c)
- zipWithM_ :: Monad m => (a -> b -> m c) -> Vector n a -> Vector n b -> m ()
- izipWithM_ :: Monad m => (Int -> a -> b -> m c) -> Vector n a -> Vector n b -> m ()
- unzip :: Vector n (a, b) -> (Vector n a, Vector n b)
- unzip3 :: Vector n (a, b, c) -> (Vector n a, Vector n b, Vector n c)
- unzip4 :: Vector n (a, b, c, d) -> (Vector n a, Vector n b, Vector n c, Vector n d)
- unzip5 :: Vector n (a, b, c, d, e) -> (Vector n a, Vector n b, Vector n c, Vector n d, Vector n e)
- unzip6 :: Vector n (a, b, c, d, e, f) -> (Vector n a, Vector n b, Vector n c, Vector n d, Vector n e, Vector n f)
- elem :: Eq a => a -> Vector n a -> Bool
- notElem :: Eq a => a -> Vector n a -> Bool
- find :: (a -> Bool) -> Vector n a -> Maybe a
- findIndex :: (a -> Bool) -> Vector n a -> Maybe Int
- elemIndex :: Eq a => a -> Vector n a -> Maybe Int
- foldl :: (a -> b -> a) -> a -> Vector n b -> a
- foldl1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a
- foldl' :: (a -> b -> a) -> a -> Vector n b -> a
- foldl1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a
- foldr :: (a -> b -> b) -> b -> Vector n a -> b
- foldr1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a
- foldr' :: (a -> b -> b) -> b -> Vector n a -> b
- foldr1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a
- ifoldl :: (a -> Int -> b -> a) -> a -> Vector n b -> a
- ifoldl' :: (a -> Int -> b -> a) -> a -> Vector n b -> a
- ifoldr :: (Int -> a -> b -> b) -> b -> Vector n a -> b
- ifoldr' :: (Int -> a -> b -> b) -> b -> Vector n a -> b
- all :: (a -> Bool) -> Vector n a -> Bool
- any :: (a -> Bool) -> Vector n a -> Bool
- and :: Vector n Bool -> Bool
- or :: Vector n Bool -> Bool
- sum :: Num a => Vector n a -> a
- product :: Num a => Vector n a -> a
- maximum :: (Ord a, KnownNat n) => Vector (n + 1) a -> a
- maximumBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> a
- minimum :: (Ord a, KnownNat n) => Vector (n + 1) a -> a
- minimumBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> a
- maxIndex :: (Ord a, KnownNat n) => Vector (n + 1) a -> Int
- maxIndexBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> Int
- minIndex :: (Ord a, KnownNat n) => Vector (n + 1) a -> Int
- minIndexBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> Int
- foldM :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m a
- ifoldM :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m a
- fold1M :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m a
- foldM' :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m a
- ifoldM' :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m a
- fold1M' :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m a
- foldM_ :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m ()
- ifoldM_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m ()
- fold1M_ :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m ()
- foldM'_ :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m ()
- ifoldM'_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m ()
- fold1M'_ :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m ()
- sequence :: Monad m => Vector n (m a) -> m (Vector n a)
- sequence_ :: Monad m => Vector n (m a) -> m ()
- prescanl :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- prescanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- postscanl :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- postscanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- scanl :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- scanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a
- scanl1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a
- scanl1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a
- prescanr :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- prescanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- postscanr :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- postscanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- scanr :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- scanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b
- scanr1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a
- scanr1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a
- toList :: Vector n a -> [a]
- fromList :: KnownNat n => [a] -> Maybe (Vector n a)
- fromListN :: forall n a. KnownNat n => [a] -> Maybe (Vector n a)
- fromListN' :: forall n a. KnownNat n => Proxy n -> [a] -> Maybe (Vector n a)
- toSized :: forall n a. KnownNat n => Vector a -> Maybe (Vector n a)
- fromSized :: Vector n a -> Vector a
- withVectorUnsafe :: (Vector a -> Vector b) -> Vector n a -> Vector n b
Documentation
Accessors
Length information
length :: forall n a. KnownNat n => Vector n a -> Int Source
O(1) Yield the length of the vector as an Int
.
length' :: forall n a. KnownNat n => Vector n a -> Proxy n Source
O(1) Yield the length of the vector as a Proxy
.
Indexing
index' :: forall n m a. (KnownNat n, KnownNat m) => Vector (n + m) a -> Proxy n -> a Source
O(1) Safe indexing using a Proxy
.
unsafeIndex :: forall n a. KnownNat n => Vector n a -> Int -> a Source
O(1) Indexing using an Int without bounds checking.
Monadic indexing
indexM :: forall n a m. (KnownNat n, Monad m) => Vector n a -> Int -> m a Source
O(1) Indexing in a monad. See the documentation for indexM
for an
explanation of why this is useful.
indexM' :: forall n k a m. (KnownNat n, KnownNat k, Monad m) => Vector (n + k) a -> Proxy n -> m a Source
unsafeIndexM :: forall n a m. (KnownNat n, Monad m) => Vector n a -> Int -> m a Source
O(1) Indexing using an Int without bounds checking. See the
documentation for indexM
for an explanation of why this is useful.
headM :: forall n a m. (KnownNat n, Monad m) => Vector (n + 1) a -> m a Source
O(1) Yield the first element of a non-empty vector in a monad. See the
documentation for indexM
for an explanation of why this is useful.
lastM :: forall n a m. (KnownNat n, Monad m) => Vector (n + 1) a -> m a Source
O(1) Yield the last element of a non-empty vector in a monad. See the
documentation for indexM
for an explanation of why this is useful.
Extracting subvectors (slicing)
O(1) Yield a slice of the vector without copying it with an inferred length argument.
:: (KnownNat i, KnownNat n) | |
=> Proxy i | starting index |
-> Proxy n | length |
-> Vector (i + n) a | |
-> Vector n a |
O(1) Yield a slice of the vector without copying it with an explicit length argument.
init :: forall n a. Vector (n + 1) a -> Vector n a Source
O(1) Yield all but the last element of a non-empty vector without copying.
tail :: forall n a. Vector (n + 1) a -> Vector n a Source
O(1) Yield all but the first element of a non-empty vector without copying.
take :: forall n m a. (KnownNat n, KnownNat m) => Vector (m + n) a -> Vector n a Source
O(1) Yield the first n elements. The resultant vector always contains this many elements. The length of the resultant vector is inferred from the type.
take' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (m + n) a -> Vector n a Source
O(1) Yield the first n elements. The resultant vector always contains
this many elements. The length of the resultant vector is given explicitly
as a Proxy
argument.
drop :: forall n m a. (KnownNat n, KnownNat m) => Vector (m + n) a -> Vector m a Source
O(1) Yield all but the the first n elements. The given vector must contain at least this many elements The length of the resultant vector is inferred from the type.
drop' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (m + n) a -> Vector m a Source
O(1) Yield all but the the first n elements. The given vector must
contain at least this many elements The length of the resultant vector is
givel explicitly as a Proxy
argument.
splitAt :: forall n m a. (KnownNat n, KnownNat m) => Vector (n + m) a -> (Vector n a, Vector m a) Source
O(1) Yield the first n elements paired with the remainder without copying. The lengths of the resultant vector are inferred from the type.
splitAt' :: forall n m a. (KnownNat n, KnownNat m) => Proxy n -> Vector (n + m) a -> (Vector n a, Vector m a) Source
O(1) Yield the first n elements paired with the remainder without
copying. The length of the first resultant vector is passed explicitly as a
Proxy
argument.
Construction
Initialization
replicate :: forall n a. KnownNat n => a -> Vector n a Source
O(n) Construct a vector with the same element in each position where the length is inferred from the type.
replicate' :: forall n a. KnownNat n => Proxy n -> a -> Vector n a Source
O(n) Construct a vector with the same element in each position where the
length is given explicitly as a Proxy
argument.
generate :: forall n a. KnownNat n => (Int -> a) -> Vector n a Source
O(n) construct a vector of the given length by applying the function to each index where the length is inferred from the type.
generate' :: forall n a. KnownNat n => Proxy n -> (Int -> a) -> Vector n a Source
O(n) construct a vector of the given length by applying the function to
each index where the length is given explicitly as a Proxy
argument.
iterateN :: forall n a. KnownNat n => (a -> a) -> a -> Vector n a Source
O(n) Apply function n times to value. Zeroth element is original value. The length is inferred from the type.
iterateN' :: forall n a. KnownNat n => Proxy n -> (a -> a) -> a -> Vector n a Source
O(n) Apply function n times to value. Zeroth element is original value.
The length is given explicitly as a Proxy
argument.
Monadic initialization
replicateM :: forall n m a. (KnownNat n, Monad m) => m a -> m (Vector n a) Source
O(n) Execute the monadic action n
times and store the results in a
vector where n
is inferred from the type.
replicateM' :: forall n m a. (KnownNat n, Monad m) => Proxy n -> m a -> m (Vector n a) Source
O(n) Execute the monadic action n
times and store the results in a
vector where n
is given explicitly as a Proxy
argument.
generateM :: forall n m a. (KnownNat n, Monad m) => (Int -> m a) -> m (Vector n a) Source
O(n) Construct a vector of length n
by applying the monadic action to
each index where n is inferred from the type.
generateM' :: forall n m a. (KnownNat n, Monad m) => Proxy n -> (Int -> m a) -> m (Vector n a) Source
O(n) Construct a vector of length n
by applying the monadic action to
each index where n is given explicitly as a Proxy
argument.
Unfolding
unfoldrN :: forall n a b. KnownNat n => (b -> (a, b)) -> b -> Vector n a Source
O(n) Construct a vector with exactly n
elements by repeatedly applying
the generator function to the a seed. The length, n
, is inferred from the
type.
unfoldrN' :: forall n a b. KnownNat n => Proxy n -> (b -> (a, b)) -> b -> Vector n a Source
O(n) Construct a vector with exactly n
elements by repeatedly applying
the generator function to the a seed. The length, n
, is given explicitly
as a Proxy
argument.
Enumeration
enumFromN :: forall n a. (KnownNat n, Num a) => a -> Vector n a Source
O(n) Yield a vector of length n
containing the values x
, x+1
etc. The length, n
, is inferred from the type.
enumFromN' :: forall n a. (KnownNat n, Num a) => a -> Proxy n -> Vector n a Source
O(n) Yield a vector of length n
containing the values x
, x+1
etc. The length, n
, is given explicitly as a Proxy
argument.
enumFromStepN :: forall n a. (KnownNat n, Num a) => a -> a -> Vector n a Source
O(n) Yield a vector of the given length containing the values x
, x+y
,
x+y+y
etc. The length, n
, is inferred from the type.
enumFromStepN' :: forall n a. (KnownNat n, Num a) => a -> a -> Proxy n -> Vector n a Source
O(n) Yield a vector of the given length containing the values x
, x+y
,
x+y+y
etc. The length, n
, is given explicitly as a Proxy
argument.
Concatenation
(++) :: forall n m a. Vector n a -> Vector m a -> Vector (n + m) a Source
O(m+n) Concatenate two vectors.
Restricting memory usage
force :: Vector n a -> Vector n a Source
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
:: Vector m a | initial vector (of length |
-> [(Int, a)] | list of index/value pairs (of length |
-> Vector m 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>
:: Vector m a | initial vector (of length |
-> Vector n (Int, a) | vector of index/value pairs (of length |
-> Vector m 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>
:: Vector m a | initial vector (of length |
-> Vector n Int | index vector (of length |
-> Vector n a | value vector (of length |
-> Vector m a |
O(m+n) 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)
:: Vector m a | initial vector (of length |
-> [(Int, a)] | list of index/value pairs (of length |
-> Vector m a |
Same as (//
) but without bounds checking.
:: Vector m a | initial vector (of length |
-> Vector n (Int, a) | vector of index/value pairs (of length |
-> Vector m a |
Same as update
but without bounds checking.
:: Vector m a | initial vector (of length |
-> Vector n Int | index vector (of length |
-> Vector n a | value vector (of length |
-> Vector m a |
Same as update_
but without bounds checking.
Accumulations
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> [(Int, b)] | list of index/value pairs (of length |
-> Vector m 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>
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> Vector n (Int, b) | vector of index/value pairs (of length |
-> Vector m 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>
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> Vector n Int | index vector (of length |
-> Vector n b | value vector (of length |
-> Vector m a |
O(m+n) 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)
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> [(Int, b)] | list of index/value pairs (of length |
-> Vector m a |
Same as accum
but without bounds checking.
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> Vector n (Int, b) | vector of index/value pairs (of length |
-> Vector m a |
Same as accumulate
but without bounds checking.
:: (a -> b -> a) | accumulating function |
-> Vector m a | initial vector (of length |
-> Vector n Int | index vector (of length |
-> Vector n b | value vector (of length |
-> Vector m a |
Same as accumulate_
but without bounds checking.
Permutations
O(n) Yield the vector obtained by replacing each element i
of the
index vector by xs
. This is equivalent to !
i
but is
often much more efficient.map
(xs!
) is
backpermute <a,b,c,d> <0,3,2,3,1,0> = <a,d,c,d,b,a>
Same as backpermute
but without bounds checking.
Elementwise operations
Indexing
Mapping
imap :: (Int -> a -> b) -> Vector n a -> Vector n b Source
O(n) Apply a function to every element of a vector and its index
concatMap :: (a -> Vector m b) -> Vector n a -> Vector (n * m) b Source
O(n*m) Map a function over a vector and concatenate the results. The function is required to always return the same length vector.
Monadic mapping
mapM :: Monad m => (a -> m b) -> Vector n a -> m (Vector n b) Source
O(n) Apply the monadic action to all elements of the vector, yielding a vector of results
imapM :: Monad m => (Int -> a -> m b) -> Vector n a -> m (Vector n b) Source
O(n) Apply the monadic action to every element of a vector and its index, yielding a vector of results
mapM_ :: Monad m => (a -> m b) -> Vector n a -> m () Source
O(n) Apply the monadic action to all elements of a vector and ignore the results
imapM_ :: Monad m => (Int -> a -> m b) -> Vector n a -> m () Source
O(n) Apply the monadic action to every element of a vector and its index, ignoring the results
forM :: Monad m => Vector n a -> (a -> m b) -> m (Vector n b) Source
O(n) Apply the monadic action to all elements of the vector, yielding a
vector of results. Equvalent to flip
.mapM
forM_ :: Monad m => Vector n a -> (a -> m b) -> m () Source
O(n) Apply the monadic action to all elements of a vector and ignore the
results. Equivalent to flip
.mapM_
Zipping
zipWith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c Source
O(n) Zip two vectors of the same length with the given function.
zipWith3 :: (a -> b -> c -> d) -> Vector n a -> Vector n b -> Vector n c -> Vector n d Source
Zip three vectors with the given function.
zipWith4 :: (a -> b -> c -> d -> e) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e Source
zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f Source
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n g Source
izipWith :: (Int -> a -> b -> c) -> Vector n a -> Vector n b -> Vector n c Source
O(n) Zip two vectors of the same length with a function that also takes the elements' indices).
izipWith3 :: (Int -> a -> b -> c -> d) -> Vector n a -> Vector n b -> Vector n c -> Vector n d Source
izipWith4 :: (Int -> a -> b -> c -> d -> e) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e Source
izipWith5 :: (Int -> a -> b -> c -> d -> e -> f) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f Source
izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n g Source
zip5 :: Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n (a, b, c, d, e) Source
zip6 :: Vector n a -> Vector n b -> Vector n c -> Vector n d -> Vector n e -> Vector n f -> Vector n (a, b, c, d, e, f) Source
Monadic zipping
zipWithM :: Monad m => (a -> b -> m c) -> Vector n a -> Vector n b -> m (Vector n c) Source
O(n) Zip the two vectors of the same length with the monadic action and yield a vector of results
izipWithM :: Monad m => (Int -> a -> b -> m c) -> Vector n a -> Vector n b -> m (Vector n c) Source
O(n) Zip the two vectors with a monadic action that also takes the element index and yield a vector of results
zipWithM_ :: Monad m => (a -> b -> m c) -> Vector n a -> Vector n b -> m () Source
O(n) Zip the two vectors with the monadic action and ignore the results
izipWithM_ :: Monad m => (Int -> a -> b -> m c) -> Vector n a -> Vector n b -> m () Source
O(n) Zip the two vectors with a monadic action that also takes the element index and ignore the results
Unzipping
unzip5 :: Vector n (a, b, c, d, e) -> (Vector n a, Vector n b, Vector n c, Vector n d, Vector n e) Source
unzip6 :: Vector n (a, b, c, d, e, f) -> (Vector n a, Vector n b, Vector n c, Vector n d, Vector n e, Vector n f) Source
Working with predicates
Searching
notElem :: Eq a => a -> Vector n a -> Bool infix 4 Source
O(n) Check if the vector does not contain an element (inverse of elem
)
Folding
foldl1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a Source
O(n) Left fold on non-empty vectors
foldl1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a Source
O(n) Left fold on non-empty vectors with strict accumulator
foldr1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a Source
O(n) Right fold on non-empty vectors
foldr1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> a Source
O(n) Right fold on non-empty vectors with strict accumulator
ifoldl :: (a -> Int -> b -> a) -> a -> Vector n b -> a Source
O(n) Left fold (function applied to each element and its index)
ifoldl' :: (a -> Int -> b -> a) -> a -> Vector n b -> a Source
O(n) Left fold with strict accumulator (function applied to each element and its index)
ifoldr :: (Int -> a -> b -> b) -> b -> Vector n a -> b Source
O(n) Right fold (function applied to each element and its index)
ifoldr' :: (Int -> a -> b -> b) -> b -> Vector n a -> b Source
O(n) Right fold with strict accumulator (function applied to each element and its index)
Specialised folds
maximum :: (Ord a, KnownNat n) => Vector (n + 1) a -> a Source
O(n) Yield the maximum element of the non-empty vector.
maximumBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> a Source
O(n) Yield the maximum element of the non-empty vector according to the given comparison function.
minimum :: (Ord a, KnownNat n) => Vector (n + 1) a -> a Source
O(n) Yield the minimum element of the non-empty vector.
minimumBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> a Source
O(n) Yield the minimum element of the non-empty vector according to the given comparison function.
maxIndex :: (Ord a, KnownNat n) => Vector (n + 1) a -> Int Source
O(n) Yield the index of the maximum element of the non-empty vector.
maxIndexBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> Int Source
O(n) Yield the index of the maximum element of the non-empty vector according to the given comparison function.
minIndex :: (Ord a, KnownNat n) => Vector (n + 1) a -> Int Source
O(n) Yield the index of the minimum element of the non-empty vector.
minIndexBy :: KnownNat n => (a -> a -> Ordering) -> Vector (n + 1) a -> Int Source
O(n) Yield the index of the minimum element of the non-empty vector according to the given comparison function.
Monadic folds
ifoldM :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m a Source
O(n) Monadic fold (action applied to each element and its index)
fold1M :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m a Source
O(n) Monadic fold over non-empty vectors
foldM' :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m a Source
O(n) Monadic fold with strict accumulator
ifoldM' :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m a Source
O(n) Monadic fold with strict accumulator (action applied to each element and its index)
fold1M' :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m a Source
O(n) Monadic fold over non-empty vectors with strict accumulator
foldM_ :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m () Source
O(n) Monadic fold that discards the result
ifoldM_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m () Source
O(n) Monadic fold that discards the result (action applied to each element and its index)
fold1M_ :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m () Source
O(n) Monadic fold over non-empty vectors that discards the result
foldM'_ :: Monad m => (a -> b -> m a) -> a -> Vector n b -> m () Source
O(n) Monadic fold with strict accumulator that discards the result
ifoldM'_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector n b -> m () Source
O(n) Monadic fold with strict accumulator that discards the result (action applied to each element and its index)
fold1M'_ :: (Monad m, KnownNat n) => (a -> a -> m a) -> Vector (n + 1) a -> m () Source
O(n) Monad fold over non-empty vectors with strict accumulator that discards the result
Monadic sequencing
sequence :: Monad m => Vector n (m a) -> m (Vector n a) Source
Evaluate each action and collect the results
Prefix sums (scans)
prescanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a Source
O(n) Prescan with strict accumulator
postscanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a Source
O(n) Scan with strict accumulator
scanl' :: (a -> b -> a) -> a -> Vector n b -> Vector n a Source
O(n) Haskell-style scan with strict accumulator
scanl1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a Source
O(n) Scan over a non-empty vector
scanl1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a Source
O(n) Scan over a non-empty vector with a strict accumulator
prescanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b Source
O(n) Right-to-left prescan with strict accumulator
postscanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b Source
O(n) Right-to-left scan with strict accumulator
scanr' :: (a -> b -> b) -> b -> Vector n a -> Vector n b Source
O(n) Right-to-left Haskell-style scan with strict accumulator
scanr1 :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a Source
O(n) Right-to-left scan over a non-empty vector
scanr1' :: KnownNat n => (a -> a -> a) -> Vector (n + 1) a -> Vector (n + 1) a Source
O(n) Right-to-left scan over a non-empty vector with a strict accumulator
Conversions
Lists
fromListN :: forall n a. KnownNat n => [a] -> Maybe (Vector n a) Source
O(n) Convert the first n
elements of a list to a vector. The length of
the resultant vector is inferred from the type.
fromListN' :: forall n a. KnownNat n => Proxy n -> [a] -> Maybe (Vector n a) Source
O(n) Convert the first n
elements of a list to a vector. The length of
the resultant vector is given explicitly as a Proxy
argument.