Safe Haskell | None |
---|
Wrappers for primitives defined in Data.Vector
.
- This is an internal API and shouldn't need to be used directly. Client programs should use Data.Array.Parallel.Unlifted.
- class (Vector Vector a, MVector MVector a) => Unbox a
- data family Vector a
- data family MVector s a
- stream :: Vector v a => v a -> Stream a
- unstream :: Vector v a => Stream a -> v a
- length :: Unbox a => Vector a -> Int
- null :: Unbox a => Vector a -> Bool
- empty :: Unbox a => Vector a
- singleton :: Unbox a => a -> Vector a
- cons :: Unbox a => a -> Vector a -> Vector a
- units :: Int -> Vector ()
- replicate :: Unbox a => Int -> a -> Vector a
- (++) :: Unbox a => Vector a -> Vector a -> Vector a
- index :: Unbox a => String -> Vector a -> Int -> a
- interleave :: Unbox e => Vector e -> Vector e -> Vector e
- indexed :: Unbox a => Vector a -> Vector (Int, a)
- repeat :: Unbox e => Int -> Vector e -> Vector e
- repeatS :: Unbox e => Int -> Vector e -> Stream e
- slice :: Unbox a => String -> Vector a -> Int -> Int -> Vector a
- unsafeSlice :: Unbox a => Vector a -> Int -> Int -> Vector a
- extract :: Unbox a => Vector a -> Int -> Int -> Vector a
- unsafeExtract :: Unbox a => Vector a -> Int -> Int -> Vector a
- tail :: Unbox a => Vector a -> Vector a
- take :: Unbox a => Int -> Vector a -> Vector a
- drop :: Unbox a => Int -> Vector a -> Vector a
- splitAt :: Unbox a => Int -> Vector a -> (Vector a, Vector a)
- permute :: Unbox e => Vector e -> Vector Int -> Vector e
- bpermute :: Unbox e => Vector e -> Vector Int -> Vector e
- mbpermute :: (Unbox e, Unbox d) => (e -> d) -> Vector e -> Vector Int -> Vector d
- bpermuteDft :: Unbox e => Int -> (Int -> e) -> Vector (Int, e) -> Vector e
- reverse :: Unbox a => Vector a -> Vector a
- update :: Unbox a => Vector a -> Vector (Int, a) -> Vector a
- map :: (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
- zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
- zipWith3 :: (Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
- filter :: Unbox a => (a -> Bool) -> Vector a -> Vector a
- pack :: Unbox e => Vector e -> Vector Bool -> Vector e
- combine :: Unbox a => Vector Bool -> Vector a -> Vector a -> Vector a
- combine2ByTag :: Unbox a => Vector Tag -> Vector a -> Vector a -> Vector a
- foldl :: Unbox a => (b -> a -> b) -> b -> Vector a -> b
- foldl1 :: Unbox a => (a -> a -> a) -> Vector a -> a
- foldl1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe a
- fold :: Unbox a => (a -> a -> a) -> a -> Vector a -> a
- fold1 :: Unbox a => (a -> a -> a) -> Vector a -> a
- fold1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe a
- scanl :: (Unbox a, Unbox b) => (b -> a -> b) -> b -> Vector a -> Vector b
- scanl1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a
- scan :: Unbox a => (a -> a -> a) -> a -> Vector a -> Vector a
- scan1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a
- scanRes :: Unbox a => (a -> a -> a) -> a -> Vector a -> (Vector a, a)
- elem :: (Unbox a, Eq a) => a -> Vector a -> Bool
- notElem :: (Unbox a, Eq a) => a -> Vector a -> Bool
- and :: Vector Bool -> Bool
- or :: Vector Bool -> Bool
- any :: Unbox a => (a -> Bool) -> Vector a -> Bool
- all :: Unbox a => (a -> Bool) -> Vector a -> Bool
- sum :: (Unbox a, Num a) => Vector a -> a
- product :: (Unbox a, Num a) => Vector a -> a
- maximum :: (Unbox a, Ord a) => Vector a -> a
- minimum :: (Unbox a, Ord a) => Vector a -> a
- maximumBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> a
- minimumBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> a
- maxIndex :: (Unbox a, Ord a) => Vector a -> Int
- minIndex :: (Unbox a, Ord a) => Vector a -> Int
- maxIndexBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> Int
- minIndexBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> Int
- zip :: (Unbox a, Unbox b) => Vector a -> Vector b -> Vector (a, b)
- unzip :: (Unbox a, Unbox b) => Vector (a, b) -> (Vector a, Vector b)
- fsts :: (Unbox a, Unbox b) => Vector (a, b) -> Vector a
- snds :: (Unbox a, Unbox b) => Vector (a, b) -> Vector b
- zip3 :: (Unbox a, Unbox b, Unbox c) => Vector a -> Vector b -> Vector c -> Vector (a, b, c)
- unzip3 :: (Unbox a, Unbox b, Unbox c) => Vector (a, b, c) -> (Vector a, Vector b, Vector c)
- enumFromTo :: (Unbox a, Enum a) => a -> a -> Vector a
- enumFromThenTo :: (Unbox a, Enum a) => a -> a -> a -> Vector a
- enumFromStepLen :: Int -> Int -> Int -> Vector Int
- enumFromToEach :: Int -> Vector (Int, Int) -> Vector Int
- enumFromStepLenEach :: Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int
- find :: Unbox a => (a -> Bool) -> Vector a -> Maybe a
- findIndex :: Unbox a => (a -> Bool) -> Vector a -> Maybe Int
- toList :: Unbox a => Vector a -> [a]
- fromList :: Unbox a => [a] -> Vector a
- random :: (Unbox a, Random a, RandomGen g) => Int -> g -> Vector a
- randomR :: (Unbox a, Random a, RandomGen g) => Int -> (a, a) -> g -> Vector a
- new :: Unbox a => Int -> (forall s. MVector s a -> ST s ()) -> Vector a
- copy :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m ()
- newM :: Unbox a => Int -> ST s (MVector s a)
- unsafeFreeze :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> m (Vector a)
- write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
- read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
- mpermute :: Unbox e => MVector s e -> Vector e -> Vector Int -> ST s ()
- mupdate :: Unbox e => MVector s e -> Vector (Int, e) -> ST s ()
- mdrop :: Unbox a => Int -> MVector s a -> MVector s a
- mslice :: Unbox a => Int -> Int -> MVector s a -> MVector s a
- class Unbox a => UIO a where
Array classes
class (Vector Vector a, MVector MVector a) => Unbox a
Unbox Bool | |
Unbox Char | |
Unbox Double | |
Unbox Float | |
Unbox Int | |
Unbox Int8 | |
Unbox Int16 | |
Unbox Int32 | |
Unbox Int64 | |
Unbox Integer | |
Unbox Ordering | |
Unbox Word | |
Unbox Word8 | |
Unbox Word16 | |
Unbox Word32 | |
Unbox Word64 | |
Unbox () | |
(Vector Vector (Complex a), MVector MVector (Complex a), RealFloat a, Unbox a) => Unbox (Complex a) | |
(Vector Vector (a, b), MVector MVector (a, b), Unbox a, Unbox b) => Unbox (a, b) | |
(Vector Vector (a, b, c), MVector MVector (a, b, c), Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) | |
(Vector Vector (a, b, c, d), MVector MVector (a, b, c, d), Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) | |
(Vector Vector (a, b, c, d, e), MVector MVector (a, b, c, d, e), Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) | |
(Vector Vector (a, b, c, d, e, f), MVector MVector (a, b, c, d, e, f), Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Unbox (a, b, c, d, e, f) |
Array types
data family Vector a
data family MVector s a
Streaming
Basic operations
replicate :: Unbox a => Int -> a -> Vector a
O(n) Vector of the given length with the same value in each position
Subarrays
tail :: Unbox a => Vector a -> Vector a
O(1) Yield all but the first element without copying. The vector may not be empty.
take :: Unbox a => Int -> Vector a -> Vector a
O(1) Yield at the first n
elements without copying. The vector may
contain less than n
elements in which case it is returned unchanged.
drop :: Unbox a => Int -> Vector a -> Vector a
O(1) Yield all but the first n
elements without copying. The vector may
contain less than n
elements in which case an empty vector is returned.
Permutations
:: Unbox a | |
=> Vector a | initial vector (of length |
-> Vector (Int, a) | vector of index/value pairs (of length |
-> Vector 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>
Higher-order operations
zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
O(min(m,n)) Zip two vectors with the given function.
zipWith3 :: (Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
Zip three vectors with the given function.
filter :: Unbox a => (a -> Bool) -> Vector a -> Vector a
O(n) Drop elements that do not satisfy the predicate
foldl1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe aSource
fold1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe aSource
Searching
notElem :: (Unbox a, Eq a) => a -> Vector a -> Bool
O(n) Check if the vector does not contain an element (inverse of elem
)
Logical operations
Arithmetic operations
maximum :: (Unbox a, Ord a) => Vector a -> a
O(n) Yield the maximum element of the vector. The vector may not be empty.
minimum :: (Unbox a, Ord a) => Vector a -> a
O(n) Yield the minimum element of the vector. The vector may not be empty.
maximumBy :: Unbox 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.
minimumBy :: Unbox 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.
maxIndex :: (Unbox a, Ord a) => Vector a -> Int
O(n) Yield the index of the maximum element of the vector. The vector may not be empty.
minIndex :: (Unbox a, Ord a) => Vector a -> Int
O(n) Yield the index of the minimum element of the vector. The vector may not be empty.
maxIndexBy :: Unbox 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.
minIndexBy :: Unbox 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.
Arrays of pairs
Enumerations
enumFromTo :: (Unbox a, Enum a) => a -> a -> Vector a
O(n) Enumerate values from x
to y
.
WARNING: This operation can be very inefficient. If at all possible, use
enumFromN
instead.
enumFromThenTo :: (Unbox a, Enum a) => a -> a -> a -> Vector 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.
Searching
Conversions to/from lists
Random arrays
Mutating operations
copy :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m ()
O(n) Copy an immutable vector into a mutable one. The two vectors must have the same length.
Mutable vectors
unsafeFreeze :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> m (Vector a)
O(1) Unsafe convert a mutable vector to an immutable one without copying. The mutable vector may not be used after this operation.
write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
Replace the element at the given position.
read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
Yield the element at the given position.