Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
An implementation of nested data parallelism (due to Simon Peyton Jones et al)
- data Equal t u where
- data ArrC t
- newArray :: [e] -> Array Int e
- inject :: Array Int e -> ArrC e
- project :: ArrC t -> Array Int t
- data Structural a t u
- data A a t u
- unA :: Category * t2 => A t2 t1 t -> Structural t2 t1 t
- mapA' :: ArrowChoice a => A a t u -> A a (ArrC t) (ArrC u)
- liftA :: Category a => a t u -> A a t u
- countA :: ArrowChoice a => A a (t, [Int]) (ArrC (t, [Int]))
- countA' :: ArrowChoice a => A a (t, Int) (ArrC (t, Int))
- splitOff :: ArrowChoice a => A a ((t1, t2), u) ((t1, u), (t2, u))
- assoc :: ArrowChoice a => A a ((t, u), v) (t, (u, v))
- indexA :: ArrowChoice a => A a (ArrC t, Int) t
- zipA :: ArrowChoice a => A a (ArrC t, ArrC u) (ArrC (t, u))
- unzipA :: ArrowChoice a => A a (ArrC (t, u)) (ArrC t, ArrC u)
- concatA :: Category a => A a (ArrC (ArrC t)) (ArrC t)
- dupA :: Category a => A a t (t, t)
- fstA :: Category a => A a (t, u) t
- sndA :: Category a => A a (t, u) u
- eval :: (?pool :: BoxedThreadPool, ArrowChoice a, Strict a, Concurrent a) => Structural a t u -> a t u
- nQueens :: Int -> A (->) () (ArrC [Int])
- sorting :: Ord t => Int -> A (->) (ArrC t) (ArrC t)
- permute :: A (->) (ArrC Int) (ArrC Int)
- dotProduct :: Num t => A (->) (ArrC t, ArrC t) t
- transpose' :: A (->) (ArrC (ArrC t)) (ArrC (ArrC t))
Documentation
Flattenable arrays
The arrows and associated operations
data Structural 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.
ArrowChoice a => ArrowChoice (A a) Source # | |
ArrowChoice a => Arrow (A a) Source # | |
(Concurrent a, Strict a, ArrowChoice a, ArrowApply a) => ArrowApply (A a) Source # | |
Category * a => Category * (A a) Source # | |
unA :: Category * t2 => A t2 t1 t -> Structural t2 t1 t Source #
Obtain a Structural
program from an A
program.
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 #
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.
eval :: (?pool :: BoxedThreadPool, ArrowChoice a, Strict a, Concurrent a) => Structural a t u -> a t u Source #
Evaluates arrows.