| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Data.Yarr.Shape
- type Work sh a = sh -> sh -> IO a
- type Walk sh a = sh -> sh -> IO a
- type Fill sh a = (sh -> IO a) -> (sh -> a -> IO ()) -> Work sh ()
- type StatefulWalk sh a s = IO s -> (sh -> IO a) -> Walk sh s
- type Foldl sh a b = (b -> sh -> a -> IO b) -> StatefulWalk sh a b
- type Foldr sh a b = (sh -> a -> b -> IO b) -> StatefulWalk sh a b
- type Block sh = (sh, sh)
- class (Eq sh, Bounded sh, Show sh, NFData sh) => Shape sh where
- class (Shape sh, Arity (BorderCount sh)) => BlockShape sh where
- type BorderCount sh
- class (Shape sh, Shape lsh) => MultiShape sh lsh | sh -> lsh, lsh -> sh where
- type Dim1 = Int
- type Dim2 = (Int, Int)
- type Dim3 = (Int, Int, Int)
- dim2BlockFill :: forall a bsx bsy. (Arity bsx, Arity bsy) => bsx -> bsy -> (a -> IO ()) -> Fill Dim2 a
- class Touchable a where
- noTouch :: a -> IO ()
Flow types hierarchy
Arguments
| = sh | Lower bound |
| -> sh | Upper bound |
| -> IO a | Result |
Abstracts interval works: Fills, Walks.
To be passed to functions from Data.Yarr.Utils.Fork module or called directly.
Arguments
| = sh | Lower bound (start for left walks, end for right ones) |
| -> sh | Upper bound (end or start) |
| -> IO a | Result |
Curried version of StatefulWalk. Identical to Work, indeed.
Arguments
| = (sh -> IO a) | Indexing function |
| -> (sh -> a -> IO ()) | Writing function |
| -> Work sh () | Curried result function -- worker |
Alias to frequently used get-write-from-to arguments combo.
To be passed as 1st parameter of all Loading functions
from Data.Yarr.Eval module.
type StatefulWalk sh a s Source #
Arguments
| = IO s | Initial state |
| -> (sh -> IO a) | Indexing function |
| -> Walk sh s | Curried result function -- walker, emits final state |
Generalizes both partially applied left and right folds, as well as walks with mutable state.
To be passed to walk runners from Data.Yarr.Walk module.
Arguments
| = (b -> sh -> a -> IO b) | Generalized left reduce |
| -> StatefulWalk sh a b | Curried result stateful walk |
Generalizes left folds.
To be passed to fold combinators from Data.Yarr.Walk module.
Arguments
| = (sh -> a -> b -> IO b) | Generalized right reduce |
| -> StatefulWalk sh a b | Curried result stateful walk |
Generalizes right folds.
To be passed to fold combinators from Data.Yarr.Walk module.
Shape and BlockShape
type Block sh = (sh, sh) Source #
Mainly for internal use. Abstracts top-left -- bottom-right pair of indices.
class (Eq sh, Bounded sh, Show sh, NFData sh) => Shape sh where Source #
Class for column-major, regular composite array indices.
Minimal complete definition
zero, size, inc, plus, offset, fromLinear, toLinear, intersect, complement, blockSize, insideBlock, makeChunkRange, foldl, unrolledFoldl, foldr, unrolledFoldr, fill, unrolledFill
Methods
0, (0, 0), (0, 0, 0)
plus :: sh -> sh -> sh Source #
(1, 2, 3) `plus` (0, 0, 1) == (1, 2, 4)
minus :: sh -> sh -> sh Source #
(1, 2) `minus` (1, 0) == (0, 2)
offset :: sh -> sh -> sh Source #
fromLinear :: sh -> Int -> sh Source #
Converts linear, memory index of shaped array to shape index without bound checks.
fromLinear (3, 4) 5 == (1, 1)
toLinear :: sh -> sh -> Int Source #
Opposite to fromLinear, converts composite array index
to linear, "memory" index without bounds checks.
toLinear (5, 5) (3, 0) == 15
intersect :: (Arity n, n ~ S n0) => VecList n sh -> sh Source #
Component-wise minimum, returns maximum legal index for all given array extents
complement :: (Arity n, n ~ S n0) => VecList n sh -> sh Source #
Component-wise maximum, used in Data.Yarr.Convolution implementation.
intersectBlocks :: (Arity n, n ~ S n0) => VecList n (Block sh) -> Block sh Source #
blockSize :: Block sh -> Int Source #
insideBlock :: Block sh -> sh -> Bool Source #
makeChunkRange :: Int -> sh -> sh -> Int -> Block sh Source #
foldl :: Foldl sh a b Source #
Standard left fold wothout unrolling.
This one and 5 following functions shouldn't be called directly,
they are intented to be passed as first argument
to Load and functions from
Data.Yarr.Work module.
unrolledFoldl :: forall a b uf. Arity uf => uf -> (a -> IO ()) -> Foldl sh a b Source #
foldr :: Foldr sh a b Source #
Standard right folding function without unrolling.
unrolledFoldr :: forall a b uf. Arity uf => uf -> (a -> IO ()) -> Foldr sh a b Source #
Standard fill without unrolling.
To avoid premature optimization just type fill
each time you want to Load array
to manifest representation.
unrolledFill :: forall a uf. Arity uf => uf -> (a -> IO ()) -> Fill sh a Source #
class (Shape sh, Arity (BorderCount sh)) => BlockShape sh where Source #
Minimal complete definition
Associated Types
type BorderCount sh Source #
Instances
class (Shape sh, Shape lsh) => MultiShape sh lsh | sh -> lsh, lsh -> sh where Source #
Instances
Shape instances
Specialized flow
Touch functions
class Touchable a where Source #
Mainly used to fight against GHC simplifier, which gives no chance to LLVM to perform Global Value Numbering optimization.
Copied from repa, see
http://hackage.haskell.org/packages/archive/repa/3.2.3.1/doc/html/Data-Array-Repa-Eval.html
Minimal complete definition
Methods
The function intented to be passed as 3rd parameter
to unrolled- functions in Shape class
and dim2BlockFill.
If your loading operation is strictly local by elements
(in most cases), use noTouch instead of this function.
Instances