yarr-1.3.1: Yet another array library

Safe HaskellNone

Data.Yarr.Shape

Contents

Synopsis

Flow types hierarchy

type Work sh aSource

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.

type Walk sh aSource

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.

type Fill sh aSource

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 sSource

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.

type Foldl sh a bSource

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.

type Foldr sh a bSource

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 whereSource

Class for column-major, regular composite array indices.

Methods

zero :: shSource

0, (0, 0), (0, 0, 0)

size :: sh -> IntSource

Dim1 size is id, size (3, 5) == 15

plus :: sh -> sh -> shSource

(1, 2, 3) `plus` (0, 0, 1) == (1, 2, 4)

minus :: sh -> sh -> shSource

(1, 2) `minus` (1, 0) == (0, 2)

offset :: sh -> sh -> shSource

offset == flip minus

fromLinearSource

Arguments

:: 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)

toLinearSource

Arguments

:: sh

Extent of array

-> sh

Shape index

-> Int

Linear index

Opposite to fromLinear, converts composite array index to linear, "memory" index without bounds checks.

id for Dim1 shapes.

toLinear (5, 5) (3, 0) == 15

intersectSource

Arguments

:: (Arity n, n ~ S n0) 
=> VecList n sh

Several array extents

-> sh

Maximum common shape index

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

foldl :: Foldl sh a bSource

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.

unrolledFoldlSource

Arguments

:: forall a b uf . Arity uf 
=> uf

Unroll factor

-> (a -> IO ())

touch or noTouch

-> Foldl sh a b

Result curried function to be passed to working functions

foldr :: Foldr sh a bSource

Standard right folding function without unrolling.

unrolledFoldrSource

Arguments

:: forall a b uf . Arity uf 
=> uf

Unroll factor

-> (a -> IO ())

touch or noTouch

-> Foldr sh a b

Result curried function to be passed to working functions

fill :: Fill sh aSource

Standard fill without unrolling. To avoid premature optimization just type fill each time you want to Load array to manifest representation.

unrolledFillSource

Arguments

:: forall a uf . Arity uf 
=> uf

Unroll factor

-> (a -> IO ())

touch or noTouch

-> Fill sh a

Result curried function to by passed to loading functions

Instances

class (Shape sh, Arity (BorderCount sh)) => BlockShape sh whereSource

For internal use.

TODO: implement for Dim3 and merge with Shape class

Associated Types

type BorderCount sh Source

Methods

clipBlockSource

Arguments

:: Block sh

Outer block

-> Block sh

Inner block

-> VecList (BorderCount sh) (Block sh)

Shavings

Shape instances

type Dim2 = (Int, Int)Source

type Dim3 = (Int, Int, Int)Source

Specialized flow

dim2BlockFillSource

Arguments

:: forall a bsx bsy . (Arity bsx, Arity bsy) 
=> bsx

Block size by x. Use n1 - n8 values.

-> bsy

Block size by y

-> (a -> IO ())

touch or noTouch

-> Fill Dim2 a

Result curried function to be passed to loading functions.

2D-unrolled filling to maximize profit from "Global value numbering" LLVM optimization.

Example:

blurred <- compute (loadS (dim2BlockFill n1 n4 touch)) delayedBlurred

Touch functions

class Touchable a whereSource

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

Methods

touch :: a -> IO ()Source

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.

noTouch :: a -> IO ()Source

Alias to (\_ -> return ()).