dph-prim-par-0.5.1.1: Parallel Primitives for Data-Parallel Haskell.

Data.Array.Parallel.Unlifted.Parallel

Description

Parallel operations on unlifted arrays

Synopsis

Documentation

data UPSegd Source

Instances

data UPSel2 Source

Contains a selector USel2, as well as an USelRep2 which says how to distribute this selector across the PEs.

See dph-prim-seq:Data.Array.Parallel.Unlifted.Sequential.Segmented.USel for more discussion of what selectors are for.

type UPSelRep2 = Dist ((Int, Int), (Int, Int))Source

A UPSelRep2 describes how to distribute the two data vectors corresponding to a UPSel2 across several PEs.

Suppose we want to perform the following combine operation:

    combine [0,0,1,1,0,1,0,0,1] [A0,A1,A2,A3,A4] [B0,B1,B2,B3] 
     = [A0,A1,B0,B1,A2,B2,A3,A4,B3]

The first array is the tags array, that says which of the data arrays to get each successive element from. As combine is difficult to compute in parallel, if we are going to perform several combines with the same tag array, we can precompute a selector that tells us where to get each element. The selector contains the original tags, as well as the source index telling us where to get each element for the result array.

    [0,0,1,1,0,1,0,0,1]      -- tags    (which data vector to take the elem from)
    [0,1,0,1,2,2,3,4,3]      -- indices (where in the vector to take the elem from)

Suppose we want to distribute the combine operation across 3 PEs. It's easy to split the selector like so:

       
     PE0                PE1               PE2
    [0,0,1]            [1,0,1]           [0,0,1]   -- tags
    [0,1,0]            [1,2,2]           [3,4,3]   -- indices

We now need to split the two data arrays. Each PE needs slices of the data arrays that correspond to the parts of the selector that were given to it. For the current example we get:

    PE0                PE1               PE2
    [A0,A1]            [A2]              [A3,A4]
    [B0]               [B1,B2]           [B3]

The UPSelRep2 contains the starting index and length of each of of these slices:

         PE0                PE1               PE2
    ((0, 0), (2, 1))   ((2, 1), (1, 2))  ((3, 3), (2, 1))
    indices   lens      indices  lens    indices  lens

updateUP :: forall a. Unbox a => Vector a -> Vector (Int, a) -> Vector aSource

enumFromToUP :: (Unbox a, Enum a) => a -> a -> Vector aSource

enumFromThenToUP :: (Unbox a, Enum a) => a -> a -> a -> Vector aSource

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

Apply a worker to all elements of a vector.

filterUP :: Unbox a => (a -> Bool) -> Vector a -> Vector aSource

Keep elements that match the given predicate.

packUP :: Unbox e => Vector e -> Vector Bool -> Vector eSource

Take elements of an array where a flag value is true, and pack them into the result.

  • The souce and flag arrays must have the same length, but this is not checked.

combineUP :: Unbox a => Vector Bool -> Vector a -> Vector a -> Vector aSource

Combine two vectors based on a selector. If the selector is true then take the element from the first vector, otherwise take it from the second.

  • The data vectors must have enough elements to satisfy the flag vector, but this is not checked.

combine2UP :: Unbox a => Vector Tag -> UPSelRep2 -> Vector a -> Vector a -> Vector aSource

Combine two vectors based on a selector.

  • The data vectors must have enough elements to satisfy the selector, but this is not checked.

TODO: What is the difference between the Tag and the UPSelRep2?

zipWithUP :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Vector a -> Vector b -> Vector cSource

Combine two vectors into a third.

foldUP :: (Unbox a, DT a) => (a -> a -> a) -> a -> Vector a -> aSource

Undirected fold. Note that this function has more constraints on its parameters than the standard fold function from the Haskell Prelude.

  • The worker function must be associative. * The provided starting element must be neutral with respect to the worker. For example 0 is neutral wrt (+) and 1 is neutral wrt (*).

We need these constraints so that we can partition the fold across several threads. Each thread folds a chunk of the input vector, then we fold together all the results in the main thread.

scanUP :: (DT a, Unbox a) => (a -> a -> a) -> a -> Vector a -> Vector aSource

Prefix scan. Similar to fold, but produce an array of the intermediate states.

  • The worker function must be associative. * The provided starting element must be neutral with respect to the worker, see foldUP for discussion.

andUP :: Vector Bool -> BoolSource

Compute the logical AND of all the elements in a array.

sumUP :: (Unbox a, DT a, Num a) => Vector a -> aSource

Compute the sum all the elements of a array.

tagsUPSel2 :: UPSel2 -> Vector TagSource

O(1). Get the tags of a selector.

indicesUPSel2 :: UPSel2 -> Vector IntSource

O(1). Get the indices of a selector.

elementsUPSel2_0 :: UPSel2 -> IntSource

O(1). TODO: What is this for?

elementsUPSel2_1 :: UPSel2 -> IntSource

O(1). TODO: What is this for?

selUPSel2 :: UPSel2 -> USel2Source

O(1). TODO: What is this for?

repUPSel2 :: UPSel2 -> UPSelRep2Source

O(1). TODO: What is this for?

mkUPSel2 :: Vector Tag -> Vector Int -> Int -> Int -> UPSelRep2 -> UPSel2Source

O(1). Construct a selector. Wrapper for UPSel2.

mkUPSelRep2 :: Vector Tag -> UPSelRep2Source

Computes a UPSelRep2 from an array of tags. This is used when parallelising a combine operation. See the docs for UPSelRep2 for details.

replicateSUP :: Unbox a => UPSegd -> Vector a -> Vector aSource

Segmented replication, using a segment descriptor.

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

Segmented replication. Each element in the vector is replicated the given number of times.

replicateRSUP 2 [1, 2, 3, 4, 5] = [1, 1, 2, 2, 3, 3, 4, 4, 5, 5]

TODO: make this efficient

appendSUPSource

Arguments

:: Unbox a 
=> UPSegd

segment descriptor of result array

-> UPSegd

segment descriptor of first array

-> Vector a

data of first array

-> UPSegd

segment descriptor of second array

-> Vector a

data of first array

-> Vector a 

Segmented append.

foldSUP :: Unbox a => (a -> a -> a) -> a -> UPSegd -> Vector a -> Vector aSource

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

fold1SUP :: Unbox a => (a -> a -> a) -> UPSegd -> Vector a -> Vector aSource

sumSUP :: (Num e, Unbox e) => UPSegd -> Vector e -> Vector eSource

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

indexedUP :: (DT e, Unbox e) => Vector e -> Vector (Int, e)Source

Associate each element of the array with its index

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

Yield an array where all elements contain the same value

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

Repeat an array the given number of times.

interleaveUP :: Unbox e => Vector e -> Vector e -> Vector eSource

Interleave elements of two arrays

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