dph-prim-par-0.7.0.1: Data Parallel Haskell segmented arrays. (production version)

Safe HaskellNone

Data.Array.Parallel.Unlifted.Distributed.Primitive

Contents

Description

Standard combinators for distributed types.

Synopsis

The Gang

data Gang Source

A Gang is a group of threads which execute arbitrary work requests.

Instances

gangSize :: Gang -> IntSource

O(1). Yield the number of threads in the Gang.

seqGang :: Gang -> GangSource

A sequential gang has no threads.

forkGang :: Int -> IO GangSource

Fork a Gang with the given number of threads (at least 1).

theGang :: GangSource

DPH programs use this single, shared gang of threads. The gang exists at top level, and is initialised at program start.

The vectoriser guarantees that the gang is only used by a single computation at a time. This is true because the program produced by the vector only uses flat parallelism, so parallel computations don't invoke further parallel computations. If the vectorised program tries to use nested parallelism then there is a bug in the vectoriser, and the code will run sequentially.

Distributed Types

class DT a whereSource

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.

Associated Types

data Dist a Source

data MDist a :: * -> *Source

Methods

indexD :: String -> 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.

deepSeqD :: a -> b -> bSource

Ensure a distributed value is fully evaluated.

sizeD :: Dist a -> IntSource

Number of elements in the distributed value.

  • For debugging only, as code shouldn't be sensitive to the return value.

sizeMD :: MDist a s -> IntSource

Number of elements in the mutable distributed value.

  • For debugging only, as code shouldn't be sensitive to the return value.

measureD :: a -> StringSource

Show a distributed value.

  • For debugging only.

Instances

DT Bool 
DT Char 
DT Double 
DT Float 
DT Int 
DT Integer 
DT Ordering 
DT Word8 
DT () 
DT UVSegd 
DT USSegd 
DT USegd 
DT a => DT (Maybe a) 
Unbox a => DT (Vector a) 
(DT a, DT b) => DT (a, b) 
(DT a, DT b, DT c) => DT (a, b, c) 

newD :: DT a => Gang -> (forall s. MDist a s -> ST s ()) -> Dist aSource

Given a computation that can write its result to a mutable distributed value, run the computation to generate an immutable distributed value.

debugD :: DT a => Dist a -> StringSource

Show all members of a distributed value.

checkGangD :: DT a => String -> Gang -> Dist a -> b -> bSource

Check that the sizes of the Gang and of the distributed value match.

Primitive Distributed Operators.

generateDSource

Arguments

:: DT a 
=> What

What is the worker function doing.

-> Gang 
-> (Int -> a) 
-> Dist a 

Create a distributed value, given a function to create the instance for each thread.

generateD_cheapSource

Arguments

:: DT a 
=> What

What is the worker function doing.

-> Gang 
-> (Int -> a) 
-> Dist a 

Create a distributed value, but do it sequentially.

This function is used when we want to operate on a distributed value, but there isn't much data involved. For example, if we want to distribute a single integer to each thread, then there's no need to fire up the gang for this.

imapD' :: (DT a, DT b) => What -> Gang -> (Int -> a -> b) -> Dist a -> Dist bSource

Map a function across all elements of a distributed value. The worker function also gets the current thread index.

foldD :: DT a => What -> Gang -> (a -> a -> a) -> Dist a -> aSource

Fold all the instances of a distributed value.

scanD :: forall a. DT a => What -> Gang -> (a -> a -> a) -> a -> Dist a -> (Dist a, a)Source

Prefix sum of the instances of a distributed value.