| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
RIO.Vector.Storable.Partial
Description
Storable Vector partial functions. Import as:
import qualified RIO.Vector.Storable.Partial as VS'
Synopsis
- (!) :: Storable a => Vector a -> Int -> a
 - head :: Storable a => Vector a -> a
 - last :: Storable a => Vector a -> a
 - indexM :: (Storable a, Monad m) => Vector a -> Int -> m a
 - headM :: (Storable a, Monad m) => Vector a -> m a
 - lastM :: (Storable a, Monad m) => Vector a -> m a
 - init :: Storable a => Vector a -> Vector a
 - tail :: Storable a => Vector a -> Vector a
 - (//) :: Storable a => Vector a -> [(Int, a)] -> Vector a
 - update_ :: Storable a => Vector a -> Vector Int -> Vector a -> Vector a
 - accum :: Storable a => (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector a
 - accumulate_ :: (Storable a, Storable b) => (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
 - backpermute :: Storable a => Vector a -> Vector Int -> Vector a
 - foldl1 :: Storable a => (a -> a -> a) -> Vector a -> a
 - foldl1' :: Storable a => (a -> a -> a) -> Vector a -> a
 - foldr1 :: Storable a => (a -> a -> a) -> Vector a -> a
 - foldr1' :: Storable a => (a -> a -> a) -> Vector a -> a
 - maximum :: (Storable a, Ord a) => Vector a -> a
 - maximumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a
 - minimum :: (Storable a, Ord a) => Vector a -> a
 - minimumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a
 - minIndex :: (Storable a, Ord a) => Vector a -> Int
 - minIndexBy :: Storable a => (a -> a -> Ordering) -> Vector a -> Int
 - maxIndex :: (Storable a, Ord a) => Vector a -> Int
 - maxIndexBy :: Storable a => (a -> a -> Ordering) -> Vector a -> Int
 - fold1M :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a
 - fold1M' :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a
 - fold1M_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m ()
 - fold1M'_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m ()
 - scanl1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
 - scanl1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a
 - scanr1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
 - scanr1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a
 
Accessors
Indexing
Monadic indexing
indexM :: (Storable a, Monad m) => Vector 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 xHere, no references to v are retained because indexing (but not the
 elements) is evaluated eagerly.
headM :: (Storable a, Monad m) => Vector a -> m a #
O(1) First element of a vector in a monad. See indexM for an
 explanation of why this is useful.
lastM :: (Storable a, Monad m) => Vector a -> m a #
O(1) Last element of a vector in a monad. See indexM for an
 explanation of why this is useful.
Extracting subvectors
init :: Storable a => Vector a -> Vector a #
O(1) Yield all but the last element without copying. The vector may not be empty.
tail :: Storable a => Vector a -> Vector a #
O(1) Yield all but the first element without copying. The vector may not be empty.
Modifying vectors
Bulk updates
Arguments
| :: Storable a | |
| => Vector a | initial vector (of length   | 
| -> [(Int, a)] | list of index/value pairs (of length   | 
| -> Vector 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>
Arguments
| :: Storable a | |
| => Vector a | initial vector (of length   | 
| -> Vector Int | index vector (of length   | 
| -> Vector a | value vector (of length   | 
| -> Vector 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>
Accumulations
Arguments
| :: Storable a | |
| => (a -> b -> a) | accumulating function   | 
| -> Vector a | initial vector (of length   | 
| -> [(Int, b)] | list of index/value pairs (of length   | 
| -> Vector a | 
O(m+n) For each pair (i,b) from the list, replace the vector element
 a at position i by f a b.
Examples
>>>import qualified Data.Vector.Storable as VS>>>VS.accum (+) (VS.fromList [1000.0,2000.0,3000.0]) [(2,4),(1,6),(0,3),(1,10)][1003.0,2016.0,3004.0]
Arguments
| :: (Storable a, Storable b) | |
| => (a -> b -> a) | accumulating function   | 
| -> Vector a | initial vector (of length   | 
| -> Vector Int | index vector (of length   | 
| -> Vector b | value vector (of length   | 
| -> Vector 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>
Permutations
Folding
foldl1' :: Storable a => (a -> a -> a) -> Vector a -> a #
O(n) Left fold on non-empty vectors with strict accumulator
foldr1' :: Storable a => (a -> a -> a) -> Vector a -> a #
O(n) Right fold on non-empty vectors with strict accumulator
Specialised folds
maximum :: (Storable a, Ord a) => Vector a -> a #
O(n) Yield the maximum element of the vector. The vector may not be empty.
Examples
>>>import qualified Data.Vector.Storable as VS>>>VS.maximum $ VS.fromList [2.0, 1.0]2.0
maximumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a #
O(n) Yield the maximum element of the vector according to the given comparison function. The vector may not be empty.
minimum :: (Storable a, Ord a) => Vector a -> a #
O(n) Yield the minimum element of the vector. The vector may not be empty.
Examples
>>>import qualified Data.Vector.Storable as VS>>>VS.minimum $ VS.fromList [2.0, 1.0]1.0
minimumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a #
O(n) Yield the minimum element of the vector according to the given comparison function. The vector may not be empty.
minIndex :: (Storable a, Ord a) => Vector a -> Int #
O(n) Yield the index of the minimum element of the vector. The vector may not be empty.
minIndexBy :: Storable a => (a -> a -> Ordering) -> Vector 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 :: (Storable a, Ord a) => Vector a -> Int #
O(n) Yield the index of the maximum element of the vector. The vector may not be empty.
maxIndexBy :: Storable a => (a -> a -> Ordering) -> Vector 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
fold1M :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a #
O(n) Monadic fold over non-empty vectors
fold1M' :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a #
O(n) Monadic fold over non-empty vectors with strict accumulator
fold1M_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m () #
O(n) Monadic fold over non-empty vectors that discards the result
fold1M'_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m () #
O(n) Monadic fold over non-empty vectors with strict accumulator that discards the result
Prefix sums (scans)
scanl1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a #
O(n) Scan over a non-empty vector
scanl f <x1,...,xn> = <y1,...,yn>
  where y1 = x1
        yi = f y(i-1) xiscanl1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a #
O(n) Scan over a non-empty vector with a strict accumulator