| dph-prim-par-0.3: Parallel Primitives for Data-Parallel Haskell. | Contents | Index |
|
Data.Array.Parallel.Unlifted.Distributed | Portability | non-portable (GHC Extensions) | Stability | experimental | Maintainer | Roman Leshchinskiy <rl@cse.unsw.edu.au> |
|
|
|
|
|
Description |
Distributed types and operations.
|
|
Synopsis |
|
data Gang | | forkGang :: Int -> IO Gang | | gangSize :: Gang -> Int | | sequentialGang :: Int -> Gang | | seqGang :: Gang -> Gang | | theGang :: Gang | | class DT a | | data Dist a | | mapD :: (DT a, DT b) => Gang -> (a -> b) -> Dist a -> Dist b | | zipWithD :: (DT a, DT b, DT c) => Gang -> (a -> b -> c) -> Dist a -> Dist b -> Dist c | | foldD :: DT a => Gang -> (a -> a -> a) -> Dist a -> a | | scanD :: DT a => Gang -> (a -> a -> a) -> a -> Dist a -> Dist a :*: a | | eqD :: (Eq a, DT a) => Gang -> Dist a -> Dist a -> Bool | | neqD :: (Eq a, DT a) => Gang -> Dist a -> Dist a -> Bool | | scalarD :: DT a => Gang -> a -> Dist a | | andD :: Gang -> Dist Bool -> Bool | | orD :: Gang -> Dist Bool -> Bool | | sumD :: (Num a, DT a) => Gang -> Dist a -> a | | zipD :: (DT a, DT b) => Dist a -> Dist b -> Dist (a :*: b) | | unzipD :: (DT a, DT b) => Dist (a :*: b) -> Dist a :*: Dist b | | fstD :: (DT a, DT b) => Dist (a :*: b) -> Dist a | | sndD :: (DT a, DT b) => Dist (a :*: b) -> Dist b | | lengthD :: UA a => Dist (UArr a) -> Dist Int | | splitLenD :: Gang -> Int -> Dist Int | | splitLengthD :: UA a => Gang -> UArr a -> Dist Int | | splitD :: UA a => Gang -> Distribution -> UArr a -> Dist (UArr a) | | joinLengthD :: UA a => Gang -> Dist (UArr a) -> Int | | joinD :: UA a => Gang -> Distribution -> Dist (UArr a) -> UArr a | | splitJoinD :: (UA a, UA b) => Gang -> (Dist (UArr a) -> Dist (UArr b)) -> UArr a -> UArr b | | data Distribution | | balanced :: Distribution | | unbalanced :: Distribution | | permuteD :: UA a => Gang -> Dist (UArr a) -> Dist (UArr Int) -> UArr a | | bpermuteD :: UA a => Gang -> UArr a -> Dist (UArr Int) -> Dist (UArr a) | | atomicUpdateD :: UA a => Gang -> Dist (UArr a) -> Dist (UArr (Int :*: a)) -> UArr a | | bpermuteSD' :: UA a => Gang -> UArr a -> Dist (SUArr Int) -> Dist (SUArr a) | | splitSD :: UA a => Gang -> Distribution -> SUArr a -> Dist (SUArr a) | | joinSD :: UA a => Gang -> Distribution -> Dist (SUArr a) -> SUArr a | | splitJoinSD :: (UA a, UA b) => Gang -> (Dist (SUArr a) -> Dist (SUArr b)) -> SUArr a -> SUArr b | | fromD :: DT a => Gang -> Dist a -> [a] | | toD :: DT a => Gang -> [a] -> Dist a |
|
|
|
Gang operations
|
|
data Gang |
A Gang is a either group of threads which execute arbitrary work
requests. A sequential Gang simulates such a group by executing work
requests sequentially.
| Instances | |
|
|
forkGang :: Int -> IO Gang |
Fork a Gang with the given number of threads (at least 1).
|
|
gangSize :: Gang -> Int |
The number of threads in the Gang.
|
|
sequentialGang :: Int -> Gang |
Yield a sequential Gang which simulates the given number of threads.
|
|
seqGang :: Gang -> Gang |
Yield a sequential Gang which simulates the given one.
|
|
Gang hacks
|
|
theGang :: Gang |
|
Distributed types and classes
|
|
class DT a |
Distributed types
----------------------------
Class of distributable types. Instances of DT can be
distributed across all workers of a Gang. All such types
must be hyperstrict as we do not want to pass thunks into distributed
computations.
| | Instances | |
|
|
data Dist a |
Instances | |
|
|
Higher-order combinators
|
|
mapD :: (DT a, DT b) => Gang -> (a -> b) -> Dist a -> Dist b |
Map a function over a distributed value.
|
|
zipWithD :: (DT a, DT b, DT c) => Gang -> (a -> b -> c) -> Dist a -> Dist b -> Dist c |
Combine two distributed values with the given function.
|
|
foldD :: DT a => Gang -> (a -> a -> a) -> Dist a -> a |
Fold a distributed value.
|
|
scanD :: DT a => Gang -> (a -> a -> a) -> a -> Dist a -> Dist a :*: a |
Prefix sum of a distributed value.
|
|
Equality
|
|
eqD :: (Eq a, DT a) => Gang -> Dist a -> Dist a -> Bool |
Test whether to distributed values are equal. This requires a Gang
and hence can't be defined in terms of Eq.
|
|
neqD :: (Eq a, DT a) => Gang -> Dist a -> Dist a -> Bool |
Test whether to distributed values are not equal. This requires a Gang
and hence can't be defined in terms of Eq.
|
|
Distributed scalars
|
|
scalarD :: DT a => Gang -> a -> Dist a |
Distribute a scalar.
|
|
andD :: Gang -> Dist Bool -> Bool |
|
orD :: Gang -> Dist Bool -> Bool |
|
sumD :: (Num a, DT a) => Gang -> Dist a -> a |
|
Distributed pairs
|
|
zipD :: (DT a, DT b) => Dist a -> Dist b -> Dist (a :*: b) |
Pairing of distributed values.
The two values must belong to the same Gang.
|
|
unzipD :: (DT a, DT b) => Dist (a :*: b) -> Dist a :*: Dist b |
Unpairing of distributed values.
|
|
fstD :: (DT a, DT b) => Dist (a :*: b) -> Dist a |
Extract the first elements of a distributed pair.
|
|
sndD :: (DT a, DT b) => Dist (a :*: b) -> Dist b |
Extract the second elements of a distributed pair.
|
|
Distributed arrays
|
|
lengthD :: UA a => Dist (UArr a) -> Dist Int |
Yield the distributed length of a distributed array.
|
|
splitLenD :: Gang -> Int -> Dist Int |
Distribute the given array length over a Gang.
|
|
splitLengthD :: UA a => Gang -> UArr a -> Dist Int |
Distribute the length of an array over a Gang.
|
|
splitD :: UA a => Gang -> Distribution -> UArr a -> Dist (UArr a) |
Distribute an array over a Gang.
|
|
joinLengthD :: UA a => Gang -> Dist (UArr a) -> Int |
Overall length of a distributed array.
|
|
joinD :: UA a => Gang -> Distribution -> Dist (UArr a) -> UArr a |
Join a distributed array.
|
|
splitJoinD :: (UA a, UA b) => Gang -> (Dist (UArr a) -> Dist (UArr b)) -> UArr a -> UArr b |
|
data Distribution |
|
balanced :: Distribution |
|
unbalanced :: Distribution |
|
Permutations
|
|
permuteD :: UA a => Gang -> Dist (UArr a) -> Dist (UArr Int) -> UArr a |
Permute for distributed arrays.
|
|
bpermuteD :: UA a => Gang -> UArr a -> Dist (UArr Int) -> Dist (UArr a) |
|
atomicUpdateD :: UA a => Gang -> Dist (UArr a) -> Dist (UArr (Int :*: a)) -> UArr a |
|
bpermuteSD' :: UA a => Gang -> UArr a -> Dist (SUArr Int) -> Dist (SUArr a) |
|
Distributed segmented arrays
|
|
splitSD :: UA a => Gang -> Distribution -> SUArr a -> Dist (SUArr a) |
|
joinSD :: UA a => Gang -> Distribution -> Dist (SUArr a) -> SUArr a |
|
splitJoinSD :: (UA a, UA b) => Gang -> (Dist (SUArr a) -> Dist (SUArr b)) -> SUArr a -> SUArr b |
|
Debugging
|
|
fromD :: DT a => Gang -> Dist a -> [a] |
Yield all elements of a distributed value.
NOTE: Debugging only.
|
|
toD :: DT a => Gang -> [a] -> Dist a |
Generate a distributed value from the first p elements of a list.
NOTE: Debugging only.
|
|
Produced by Haddock version 2.4.2 |