Safe Haskell | None |
---|
- 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
- zero :: sh
- size :: sh -> Int
- inc :: sh -> sh
- plus :: sh -> sh -> sh
- minus :: sh -> sh -> sh
- offset :: sh -> sh -> sh
- fromLinear :: sh -> Int -> sh
- toLinear :: sh -> sh -> Int
- intersect :: (Arity n, n ~ S n0) => VecList n sh -> sh
- complement :: (Arity n, n ~ S n0) => VecList n sh -> sh
- intersectBlocks :: (Arity n, n ~ S n0) => VecList n (Block sh) -> Block sh
- blockSize :: Block sh -> Int
- insideBlock :: Block sh -> sh -> Bool
- makeChunkRange :: Int -> sh -> sh -> Int -> Block sh
- foldl :: Foldl sh a b
- unrolledFoldl :: forall a b uf. Arity uf => uf -> (a -> IO ()) -> Foldl sh a b
- foldr :: Foldr sh a b
- unrolledFoldr :: forall a b uf. Arity uf => uf -> (a -> IO ()) -> Foldr sh a b
- fill :: Fill sh a
- unrolledFill :: forall a uf. Arity uf => uf -> (a -> IO ()) -> Fill sh a
- class (Shape sh, Arity (BorderCount sh)) => BlockShape sh where
- type BorderCount sh
- clipBlock :: Block sh -> Block sh -> VecList (BorderCount sh) (Block 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
= sh | Lower bound |
-> sh | Upper bound |
-> IO a | Result |
Abstracts interval works: Fill
s, Walk
s.
To be passed to functions from Data.Yarr.Utils.Fork module or called directly.
= 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.
= (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 Load
ing functions
from Data.Yarr.Eval module.
type StatefulWalk sh a sSource
= 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.
= (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.
= (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 whereSource
Class for column-major, regular composite array indices.
0
, (0, 0)
, (0, 0, 0)
(1, 2, 3) `plus` (0, 0, 1) == (1, 2, 4)
(1, 2) `minus` (1, 0) == (0, 2)
offset :: sh -> sh -> shSource
:: sh | Extent of array |
-> Int | Linear index |
-> sh | Shape index |
Converts linear, memory index of shaped array to shape index without bound checks.
fromLinear (3, 4) 5 == (1, 1)
:: sh | Extent of array |
-> sh | Shape index |
-> Int | Linear index |
Opposite to fromLinear
, converts composite array index
to linear, "memory" index without bounds checks.
toLinear (5, 5) (3, 0) == 15
Component-wise minimum, returns maximum legal index for all given array extents
complement :: (Arity n, n ~ S n0) => VecList n sh -> shSource
Component-wise maximum, used in Data.Yarr.Convolution implementation.
intersectBlocks :: (Arity n, n ~ S n0) => VecList n (Block sh) -> Block shSource
blockSize :: Block sh -> IntSource
insideBlock :: Block sh -> sh -> BoolSource
makeChunkRange :: Int -> sh -> sh -> Int -> Block shSource
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.
:: forall a b uf . Arity uf | |
=> uf | Unroll factor |
-> (a -> IO ()) | |
-> Foldl sh a b | Result curried function to be passed to working functions |
Standard right folding function without unrolling.
:: forall a b uf . Arity uf | |
=> uf | Unroll factor |
-> (a -> IO ()) | |
-> Foldr sh a b | Result curried function to be passed to working functions |
Standard fill without unrolling.
To avoid premature optimization just type fill
each time you want to Load
array
to manifest representation.
class (Shape sh, Arity (BorderCount sh)) => BlockShape sh whereSource
type BorderCount sh Source
:: Block sh | Outer block |
-> Block sh | Inner block |
-> VecList (BorderCount sh) (Block sh) | Shavings |
class (Shape sh, Shape lsh) => MultiShape sh lsh | sh -> lsh, lsh -> sh whereSource
Shape instances
Specialized flow
Touch functions
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
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.