ConcurrentUtils-0.4.5.0: Concurrent utilities

Safe HaskellTrustworthy
LanguageHaskell98

Control.CUtils.DataParallel

Contents

Description

An implementation of nested data parallelism (due to Simon Peyton Jones et al)

Synopsis

Documentation

data Equal t u where Source #

Constructors

Equal :: Equal t t 

Flattenable arrays

data ArrC t Source #

Instances

Functor ArrC Source # 

Methods

fmap :: (a -> b) -> ArrC a -> ArrC b #

(<$) :: a -> ArrC b -> ArrC a #

newArray :: [e] -> Array Int e Source #

The arrows and associated operations

data Structural a t u Source #

Instances

Category * a => Category * (Structural a) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Show (Structural a t u) Source # 

Methods

showsPrec :: Int -> Structural a t u -> ShowS #

show :: Structural a t u -> String #

showList :: [Structural a t u] -> ShowS #

data A a t u Source #

The A arrow includes a set of primitives that may be executed concurrently. Programs are incrementally optimized as they are put together. A program may be optimized once, and the result saved for repeated use.

Notes:

  • The exact output of the optimizer is subject to change.
  • The program must be a finite data structure, or optimization may diverge. Therefore recursive definitions do not work, unless something is done to limit the depth.

Instances

ArrowChoice a => ArrowChoice (A a) Source # 

Methods

left :: A a b c -> A a (Either b d) (Either c d) #

right :: A a b c -> A a (Either d b) (Either d c) #

(+++) :: A a b c -> A a b' c' -> A a (Either b b') (Either c c') #

(|||) :: A a b d -> A a c d -> A a (Either b c) d #

ArrowChoice a => Arrow (A a) Source # 

Methods

arr :: (b -> c) -> A a b c #

first :: A a b c -> A a (b, d) (c, d) #

second :: A a b c -> A a (d, b) (d, c) #

(***) :: A a b c -> A a b' c' -> A a (b, b') (c, c') #

(&&&) :: A a b c -> A a b c' -> A a b (c, c') #

(Concurrent a, Strict a, ArrowChoice a, ArrowApply a) => ArrowApply (A a) Source # 

Methods

app :: A a (A a b c, b) c #

Category * a => Category * (A a) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

unA :: Category * t2 => A t2 t1 t -> Structural t2 t1 t Source #

Obtain a Structural program from an A program.

mapA' :: ArrowChoice a => A a t u -> A a (ArrC t) (ArrC u) Source #

liftA :: Category a => a t u -> A a t u Source #

countA :: ArrowChoice a => A a (t, [Int]) (ArrC (t, [Int])) Source #

Supplies an array of a repeated value paired with the index of each element. Arguably adjacent countAs should fuse; however this is hard to implement, so I have opted to provide a more powerful countA that works on arrays of indices; it generates arrays of indices lexicographically ordered.

countA' :: ArrowChoice a => A a (t, Int) (ArrC (t, Int)) Source #

splitOff :: ArrowChoice a => A a ((t1, t2), u) ((t1, u), (t2, u)) Source #

assoc :: ArrowChoice a => A a ((t, u), v) (t, (u, v)) Source #

indexA :: ArrowChoice a => A a (ArrC t, Int) t Source #

Access one index of an array.

zipA :: ArrowChoice a => A a (ArrC t, ArrC u) (ArrC (t, u)) Source #

An operation analogous to zip, zipA combines two packed arrays into a single array element by element.

unzipA :: ArrowChoice a => A a (ArrC (t, u)) (ArrC t, ArrC u) Source #

unzipA and zipA are inverses.

concatA :: Category a => A a (ArrC (ArrC t)) (ArrC t) Source #

Concatenation flattens out nested layers of arrays. The key operation used to implement is erasing marks; erasing marks throws away the structure that would delineate the edges of arrays; effectively flattening them into one array. The operation is divided into packing and erasing marks, in the hope that the packing stage will fuse with an adjacent unpack.

dupA :: Category a => A a t (t, t) Source #

Replacements for common arrow functions make fusing work better.

fstA :: Category a => A a (t, u) t Source #

sndA :: Category a => A a (t, u) u Source #

eval :: (?pool :: BoxedThreadPool, ArrowChoice a, Strict a, Concurrent a) => Structural a t u -> a t u Source #

Evaluates arrows.

Examples

nQueens :: Int -> A (->) () (ArrC [Int]) Source #

sorting :: Ord t => Int -> A (->) (ArrC t) (ArrC t) Source #

dotProduct :: Num t => A (->) (ArrC t, ArrC t) t Source #

transpose' :: A (->) (ArrC (ArrC t)) (ArrC (ArrC t)) Source #

Orphan instances

Show (t -> u) Source # 

Methods

showsPrec :: Int -> (t -> u) -> ShowS #

show :: (t -> u) -> String #

showList :: [t -> u] -> ShowS #