yarr-0.9.1: Yet another array library

Safe HaskellNone

Data.Yarr.Shape

Synopsis

Documentation

type Fill sh aSource

Arguments

 = (sh -> IO a)

Get

-> (sh -> a -> IO ())

Write

-> sh

Start

-> sh

End

-> IO () 

Alias to frequently used get-write-from-to arguments combo.

Passed as 1st parameter of all Loading functions from Data.Yarr.Eval module.

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

foldlSource

Arguments

:: (b -> sh -> a -> IO b)

Generalized reduce

-> b

Zero

-> (sh -> IO a)

Get

-> sh

Start

-> sh

End

-> IO b

Result

Following 6 functions shouldn't be called directly, they are intented to be passed as first argument to Load and not currently existring Fold functions.

unrolledFoldlSource

Arguments

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

Unroll factor

-> (a -> IO ())

touch or noTouch

-> (b -> sh -> a -> IO b)

Generalized reduce

-> b

Zero

-> (sh -> IO a)

Get

-> sh

Start

-> sh

End

-> IO b

Result

foldrSource

Arguments

:: (sh -> a -> b -> IO b)

Generalized reduce

-> b

Zero

-> (sh -> IO a)

Get

-> sh

Start

-> sh

End

-> IO b

Result

unrolledFoldrSource

Arguments

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

Unroll factor

-> (a -> IO ())

touch or noTouch

-> (sh -> a -> b -> IO b)

Generalized reduce

-> b

Zero

-> (sh -> IO a)

Get

-> sh

Start

-> sh

End

-> IO b

Result

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 pass 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

type Dim2 = (Int, Int)Source

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 pass to loading functions.

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

Example:

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

type Dim3 = (Int, Int, Int)Source