Data.Array.Parallel.Unlifted.Distributed
Contents
Description
Distributed types and operations.
- data Gang
 - forkGang :: Int -> IO Gang
 - gangSize :: Gang -> Int
 - theGang :: Gang
 - class  DT a  where
- data Dist a
 - data MDist a :: * -> *
 - indexD :: Dist a -> Int -> a
 - newMD :: Gang -> ST s (MDist a s)
 - readMD :: MDist a s -> Int -> ST s a
 - writeMD :: MDist a s -> Int -> a -> ST s ()
 - unsafeFreezeMD :: MDist a s -> ST s (Dist a)
 - deepSeqD :: a -> b -> b
 - sizeD :: Dist a -> Int
 - sizeMD :: MDist a s -> Int
 - measureD :: a -> String
 
 - 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 :: forall a. 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 :: Unbox a => Dist (Vector a) -> Dist Int
 - splitLenD :: Gang -> Int -> Dist Int
 - splitLenIdxD :: Gang -> Int -> Dist (Int, Int)
 - splitD :: Unbox a => Gang -> Distribution -> Vector a -> Dist (Vector a)
 - splitAsD :: Unbox a => Gang -> Dist Int -> Vector a -> Dist (Vector a)
 - joinLengthD :: Unbox a => Gang -> Dist (Vector a) -> Int
 - joinD :: Unbox a => Gang -> Distribution -> Dist (Vector a) -> Vector a
 - splitJoinD :: (Unbox a, Unbox b) => Gang -> (Dist (Vector a) -> Dist (Vector b)) -> Vector a -> Vector b
 - joinDM :: Unbox a => Gang -> Dist (Vector a) -> ST s (MVector s a)
 - splitSegdD :: Gang -> USegd -> Dist USegd
 - splitSegdD' :: Gang -> USegd -> Dist ((USegd, Int), Int)
 - splitSD :: Unbox a => Gang -> Dist USegd -> Vector a -> Dist (Vector a)
 - lengthUSegdD :: Dist USegd -> Dist Int
 - lengthsUSegdD :: Dist USegd -> Dist (Vector Int)
 - indicesUSegdD :: Dist USegd -> Dist (Vector Int)
 - elementsUSegdD :: Dist USegd -> Dist Int
 - data Distribution
 - balanced :: Distribution
 - unbalanced :: Distribution
 - permuteD :: forall a. Unbox a => Gang -> Dist (Vector a) -> Dist (Vector Int) -> Vector a
 - bpermuteD :: Unbox a => Gang -> Vector a -> Dist (Vector Int) -> Dist (Vector a)
 - atomicUpdateD :: forall a. Unbox a => Gang -> Dist (Vector a) -> Dist (Vector (Int, a)) -> Vector a
 - fromD :: DT a => Gang -> Dist a -> [a]
 - toD :: DT a => Gang -> [a] -> Dist a
 - debugD :: DT a => Dist a -> String
 
Gang operations
A Gang is a group of threads which execute arbitrary work requests.
   To get the gang to do work, write Req-uest values
   to its MVars
Gang hacks
Distributed types and classes
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.
Methods
indexD :: Dist a -> Int -> aSource
Extract a single element of an immutable distributed value.
newMD :: Gang -> ST s (MDist a s)Source
Create an unitialised distributed value for the given Gang.
   The gang is used (only) to know how many elements are needed
   in the distributed value.
readMD :: MDist a s -> Int -> ST s aSource
Extract an element from a mutable distributed value.
writeMD :: MDist a s -> Int -> a -> ST s ()Source
Write an element of a mutable distributed value.
unsafeFreezeMD :: MDist a s -> ST s (Dist a)Source
Unsafely freeze a mutable distributed value.
Number of elements in the distributed value. For debugging only, as we shouldn't depend on the size of the gang.
sizeMD :: MDist a s -> IntSource
Number of elements in the mutable distributed value. For debugging only, as we shouldn't care about the actual number.
Show a distributed value. For debugging only.
Higher-order combinators
mapD :: (DT a, DT b) => Gang -> (a -> b) -> Dist a -> Dist bSource
Map a function over a distributed value.
zipWithD :: (DT a, DT b, DT c) => Gang -> (a -> b -> c) -> Dist a -> Dist b -> Dist cSource
Combine two distributed values with the given function.
scanD :: forall a. DT a => Gang -> (a -> a -> a) -> a -> Dist a -> (Dist a, a)Source
Prefix sum of a distributed value.
Equality
Distributed scalars
scalarD :: DT a => Gang -> a -> Dist aSource
Distribute a scalar. Each thread gets its own copy of the same value.
Distributed pairs
zipD :: (DT a, DT b) => Dist a -> Dist b -> Dist (a, b)Source
Pairing of distributed values.
 The two values must belong to the same Gang.
fstD :: (DT a, DT b) => Dist (a, b) -> Dist aSource
Extract the first elements of a distributed pair.
sndD :: (DT a, DT b) => Dist (a, b) -> Dist bSource
Extract the second elements of a distributed pair.
Distributed arrays
lengthD :: Unbox a => Dist (Vector a) -> Dist IntSource
Yield the distributed length of a distributed array.
splitLenD :: Gang -> Int -> Dist IntSource
Distribute an array length over a Gang.
   Each thread holds the number of elements it's reponsible for.
splitLenIdxD :: Gang -> Int -> Dist (Int, Int)Source
Distribute an array length over a Gang.
   Each thread holds the number of elements it's responsible for, 
   and the index of the start of its chunk.
splitD :: Unbox a => Gang -> Distribution -> Vector a -> Dist (Vector a)Source
Distribute an array over a Gang.
NOTE: This is defined in terms of splitD_impl to avoid introducing loops through RULES. Without it, splitJoinD would be a loop breaker.
splitAsD :: Unbox a => Gang -> Dist Int -> Vector a -> Dist (Vector a)Source
Distribute an array over a Gang such that each threads gets the given
   number of elements.
joinLengthD :: Unbox a => Gang -> Dist (Vector a) -> IntSource
Get the overall length of a distributed array. We ask each thread for its chunk length, and sum them all up.
joinD :: Unbox a => Gang -> Distribution -> Dist (Vector a) -> Vector aSource
Join a distributed array.
NOTE: This is defined in terms of joinD_impl to avoid introducing loops through RULES. Without it, splitJoinD would be a loop breaker.
splitJoinD :: (Unbox a, Unbox b) => Gang -> (Dist (Vector a) -> Dist (Vector b)) -> Vector a -> Vector bSource
Split a vector over a gang, run a distributed computation, then join the pieces together again.
joinDM :: Unbox a => Gang -> Dist (Vector a) -> ST s (MVector s a)Source
Join a distributed array, yielding a mutable global array
data Distribution Source
This is a phantom parameter used to record whether a distributed value is balanced evenly among the threads. It's used to signal this property between RULES, but the actual value is never used.
Permutations
permuteD :: forall a. Unbox a => Gang -> Dist (Vector a) -> Dist (Vector Int) -> Vector aSource
Permute for distributed arrays.
atomicUpdateD :: forall a. Unbox a => Gang -> Dist (Vector a) -> Dist (Vector (Int, a)) -> Vector aSource
Debugging
fromD :: DT a => Gang -> Dist a -> [a]Source
Yield all elements of a distributed value. NOTE: For debugging only, don't use in production code.