dph-prim-seq-0.6.1.1: Data Parallel Haskell segmented arrays. (sequential implementation)

Safe HaskellSafe-Infered

Data.Array.Parallel.Unlifted.Sequential.Vector

Contents

Description

Wrappers for primitives defined in Data.Vector.

Synopsis

Array classes

class (Vector Vector a, MVector MVector a) => Unbox a

Instances

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 () 
(RealFloat a, Unbox a) => Unbox (Complex a) 
(Unbox a, Unbox b) => Unbox (a, b) 
(Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) 
(Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) 
(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) 
(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

stream :: Vector v a => v a -> Stream a

O(1) Convert a vector to a Stream

unstream :: Vector v a => Stream a -> v a

O(n) Construct a vector from a Stream

Basic operations

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

O(1) Yield the length of the vector.

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

O(1) Test whether a vector if empty

empty :: Unbox a => Vector a

O(1) Empty vector

singleton :: Unbox a => a -> Vector a

O(1) Vector with exactly one element

cons :: Unbox a => a -> Vector a -> Vector a

O(n) Prepend an element

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

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

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

O(m+n) Concatenate two vectors

index :: Unbox a => String -> Vector a -> Int -> aSource

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

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

repeat :: Unbox e => Int -> Vector e -> Vector eSource

repeatS :: Unbox e => Int -> Vector e -> Stream eSource

Subarrays

slice :: Unbox a => String -> Vector a -> Int -> Int -> Vector aSource

extract :: Unbox a => Vector a -> Int -> Int -> Vector aSource

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.

splitAt :: Unbox a => Int -> Vector a -> (Vector a, Vector a)

O(1) Yield the first n elements paired with the remainder without copying.

Note that splitAt n v is equivalent to (take n v, drop n v) but slightly more efficient.

Permutations

mbpermute :: (Unbox e, Unbox d) => (e -> d) -> Vector e -> Vector Int -> Vector dSource

bpermuteDft :: Unbox e => Int -> (Int -> e) -> Vector (Int, e) -> Vector eSource

reverse :: Unbox a => Vector a -> Vector a

O(n) Reverse a vector

update

Arguments

:: Unbox a 
=> Vector a

initial vector (of length m)

-> Vector (Int, a)

vector of index/value pairs (of length n)

-> 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

map :: (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b

O(n) Map a function over a vector

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

foldl :: Unbox a => (b -> a -> b) -> b -> Vector a -> bSource

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

foldl1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe aSource

fold :: Unbox a => (a -> a -> a) -> a -> Vector a -> aSource

fold1 :: Unbox a => (a -> a -> a) -> Vector a -> aSource

fold1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe aSource

scanl :: (Unbox a, Unbox b) => (b -> a -> b) -> b -> Vector a -> Vector bSource

scanl1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector aSource

scan :: Unbox a => (a -> a -> a) -> a -> Vector a -> Vector aSource

scan1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector aSource

scanRes :: Unbox a => (a -> a -> a) -> a -> Vector a -> (Vector a, a)Source

Searching

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

O(n) Check if the vector contains an element

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

and :: Vector Bool -> Bool

O(n) Check if all elements are True

or :: Vector Bool -> Bool

O(n) Check if any element is True

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

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

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

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

Arithmetic operations

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

O(n) Compute the sum of the elements

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

O(n) Compute the produce of the elements

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

zip :: (Unbox a, Unbox b) => Vector a -> Vector b -> Vector (a, b)Source

unzip :: (Unbox a, Unbox b) => Vector (a, b) -> (Vector a, Vector b)Source

fsts :: (Unbox a, Unbox b) => Vector (a, b) -> Vector aSource

snds :: (Unbox a, Unbox b) => Vector (a, b) -> Vector bSource

zip3 :: (Unbox a, Unbox b, Unbox c) => Vector a -> Vector b -> Vector c -> Vector (a, b, c)Source

unzip3 :: (Unbox a, Unbox b, Unbox c) => Vector (a, b, c) -> (Vector a, Vector b, Vector c)Source

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

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

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

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

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

Conversions to/from lists

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

O(n) Convert a vector to a list

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

O(n) Convert a list to a vector

Random arrays

random :: (Unbox a, Random a, RandomGen g) => Int -> g -> Vector aSource

randomR :: (Unbox a, Random a, RandomGen g) => Int -> (a, a) -> g -> Vector aSource

Mutating operations

new :: Unbox a => Int -> (forall s. MVector s a -> ST s ()) -> Vector aSource

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

newM :: Unbox a => Int -> ST s (MVector s a)Source

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.

mpermute :: Unbox e => MVector s e -> Vector e -> Vector Int -> ST s ()Source

mupdate :: Unbox e => MVector s e -> Vector (Int, e) -> ST s ()Source

mdrop :: Unbox a => Int -> MVector s a -> MVector s aSource

mslice :: Unbox a => Int -> Int -> MVector s a -> MVector s aSource

I/O

class Unbox a => UIO a whereSource

Methods

hPut :: Handle -> Vector a -> IO ()Source

hGet :: Handle -> IO (Vector a)Source

Instances

UIO Double 
UIO Int 
(UIO a, UIO b) => UIO (a, b)