| Safe Haskell | None |
|---|
Data.Yarr.Convolution
- data CV
- data CVL
- justCenter :: Shape sh => UArray CV CVL sh a -> UArray D SH sh a
- data Dim1Stencil size a b c = Dim1Stencil {
- dim1StencilSize :: size
- dim1StencilValues :: VecList size b
- dim1StencilReduce :: c -> a -> b -> IO c
- dim1StencilZero :: IO c
- dim1St :: QuasiQuoter
- dConvolveDim1WithStaticStencil :: (StencilOffsets s so eo, USource r l Dim1 a) => Dim1Stencil s a b c -> UArray r l Dim1 a -> UArray CV CVL Dim1 c
- convolveDim1WithStaticStencil :: forall r l s so eo a b c. (USource r l Dim1 a, StencilOffsets s so eo) => (UArray r l Dim1 a -> Dim1 -> Dim1 -> IO a) -> Dim1Stencil s a b c -> UArray r l Dim1 a -> UArray CV CVL Dim1 c
- data Dim2Stencil sx sy a b c = Dim2Stencil {
- dim2StencilSizeX :: sx
- dim2StencilSizeY :: sy
- dim2StencilValues :: VecList sy (VecList sx b)
- dim2StencilReduce :: c -> a -> b -> IO c
- dim2StencilZero :: IO c
- dim2St :: QuasiQuoter
- dim2OutClamp :: USource r l Dim2 a => UArray r l Dim2 a -> Dim2 -> Dim2 -> IO a
- dConvolveShDim2WithStaticStencil :: (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r SH Dim2 a) => Dim2Stencil sx sy a b c -> UArray r SH Dim2 a -> UArray CV CVL Dim2 c
- convolveShDim2WithStaticStencil :: forall r sx sox eox sy soy eoy a b c. (USource r SH Dim2 a, StencilOffsets sx sox eox, StencilOffsets sy soy eoy) => (UArray r SH Dim2 a -> Dim2 -> Dim2 -> IO a) -> Dim2Stencil sx sy a b c -> UArray r SH Dim2 a -> UArray CV CVL Dim2 c
- dConvolveLinearDim2WithStaticStencil :: (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r L Dim2 a) => Dim2Stencil sx sy a b c -> UArray r L Dim2 a -> UArray CV CVL Dim2 c
- convolveLinearDim2WithStaticStencil :: forall r sx sox eox sy soy eoy a b c. (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r L Dim2 a) => (UArray r L Dim2 a -> Dim2 -> Dim2 -> IO a) -> Dim2Stencil sx sy a b c -> UArray r L Dim2 a -> UArray CV CVL Dim2 c
Convoluted representation
Convolution fused representation internally keeps 2 element getters:
- slow border get, which checks every index from applied stencil to lay inside extent of underlying source array.
- fast center get, which doesn't worry about bound checks
and center Block.
Instances
| Shape sh => USource CV CVL sh a | |
| Shape sh => Regular CV CVL sh a | |
| Shape sh => DefaultFusion CV CV CVL sh | |
| Shape sh => DefaultIFusion CV CVL CV CVL sh | |
| Shape sh => IFusion CV CVL CV CVL sh | |
| (BlockShape sh, UTarget tr tl sh a) => RangeLoad CV CVL tr tl sh a | |
| (BlockShape sh, UTarget tr tl sh a) => Load CV CVL tr tl sh a | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => RangeVecLoad (SE CV) CV CVL tr tslr tl sh v v2 e | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => VecLoad (SE CV) CV CVL tr tslr tl sh v v2 e | |
| Shape sh => NFData (UArray CV CVL sh a) |
ConVolution Load type is specialized to load convoluted arrays.
It loads center with centerGet and borders outside the center with
borderGet separately.
It is even able to distribute quite expensive border loads evenly between available threads while parallel load.
Element-wise Loading convoluted arrays wasn't inlined propely
with unrolled Filling (unrolledFill, dim2BlockFill).
However, with simple fill performance was OK.
For details see http://stackoverflow.com/questions/14748900/ghc-doesnt-perform-2-stage-partial-application-inlining
ALMOST SOLVED: you just need to support unrolled filling function with INLINE pragma,
see https://github.com/leventov/yarr/blob/master/tests/blur.hs,
ffill function.
Instances
| Shape sh => PreferredWorkIndex CVL sh sh | |
| Shape sh => USource CV CVL sh a | |
| Shape sh => Regular CV CVL sh a | |
| Shape sh => DefaultFusion CV CV CVL sh | |
| Shape sh => DefaultIFusion CV CVL CV CVL sh | |
| Shape sh => IFusion CV CVL CV CVL sh | |
| (BlockShape sh, UTarget tr tl sh a) => RangeLoad CV CVL tr tl sh a | |
| (BlockShape sh, UTarget tr tl sh a) => Load CV CVL tr tl sh a | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => RangeVecLoad (SE CV) CV CVL tr tslr tl sh v v2 e | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => VecLoad (SE CV) CV CVL tr tslr tl sh v v2 e | |
| Shape sh => NFData (UArray CV CVL sh a) |
justCenter :: Shape sh => UArray CV CVL sh a -> UArray D SH sh aSource
Retreives fast center get from convoluted array
and wraps it into Delayed array.
Remember that array indexing in Yarr is always zero-based, so indices in result array are shifted by top-level corner offset of given convoluted array.
There is also Convoluted UArray family constructor,
which isn't presented in the docs because Haddock
doesn't support associated family constructors.
See source of Data.Yarr.Convolution.Repr module.
Static stencils
Dim1 stencils
data Dim1Stencil size a b c Source
Generalized static Dim1 stencil.
Constructors
| Dim1Stencil | |
Fields
| |
QuasiQuoter for producing typical numeric convolving Dim1 stencil,
which effectively skips unnecessary multiplications.
[dim1St| 1 4 6 4 1 |]
Produces
Dim1Stenciln5(VecList[\ acc a -> return (acc + a), \ acc a -> (return $ (acc + (4 * a))), \ acc a -> (return $ (acc + (6 * a))), \ acc a -> (return $ (acc + (4 * a))), \ acc a -> return (acc + a)]) (\ acc a reduce -> reduce acc a) (return 0)
dConvolveDim1WithStaticStencilSource
Arguments
| :: (StencilOffsets s so eo, USource r l Dim1 a) | |
| => Dim1Stencil s a b c | Convolution stencil |
| -> UArray r l Dim1 a | Source array |
| -> UArray CV CVL Dim1 c | Fused convolved result array |
Curried version of convolveDim1WithStaticStencil
with border get clamping indices out of bounds to
0 or (.
extent source)
convolveDim1WithStaticStencilSource
Arguments
| :: forall r l s so eo a b c . (USource r l Dim1 a, StencilOffsets s so eo) | |
| => (UArray r l Dim1 a -> Dim1 -> Dim1 -> IO a) | (Source array -> Extent of this array -> Index (may be out of bounds) -> Result value): Border index (to treat indices near to bounds) |
| -> Dim1Stencil s a b c | Convolution stencil |
| -> UArray r l Dim1 a | Source array |
| -> UArray CV CVL Dim1 c | Fused convolved result array |
Convolves Dim1 array with static stencil.
Dim2 stencils
data Dim2Stencil sx sy a b c Source
Generalized static Dim2 stencil.
Constructors
| Dim2Stencil | |
Fields
| |
Most useful Dim2 stencil producer.
Typing
[dim2St| 1 2 1
0 0 0
-1 -2 -1 |]
Results to
Dim2Stenciln3n3(VecList[VecList[\ acc a -> return (acc + a), \ acc a -> (return $ (acc + (2 * a))), \ acc a -> return (acc + a)],VecList[\ acc _ -> return acc, \ acc _ -> return acc, \ acc _ -> return acc],VecList[\ acc a -> return (acc - a), \ acc a -> (return $ (acc + (-2 * a))), \ acc a -> return (acc - a)]]) (\ acc a reduce -> reducej acc a) (return 0)
dim2OutClamp :: USource r l Dim2 a => UArray r l Dim2 a -> Dim2 -> Dim2 -> IO aSource
Clamps Dim2 index out of bounds to the nearest one inside bounds.
dConvolveShDim2WithStaticStencilSource
Arguments
| :: (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r SH Dim2 a) | |
| => Dim2Stencil sx sy a b c | Convolution stencil |
| -> UArray r SH Dim2 a | Source array |
| -> UArray CV CVL Dim2 c | Fused convolved result array |
Defined as
dConvolveShDim2WithStaticStencil =
convolveShDim2WithStaticStencil dim2OutClamp
Example:
let gradientX =
dConvolveLinearDim2WithStaticStencil
[dim2St| -1 0 1
-2 0 2
-1 0 1 |]
image
convolveShDim2WithStaticStencilSource
Arguments
| :: forall r sx sox eox sy soy eoy a b c . (USource r SH Dim2 a, StencilOffsets sx sox eox, StencilOffsets sy soy eoy) | |
| => (UArray r SH Dim2 a -> Dim2 -> Dim2 -> IO a) | (Source array -> Extent of this array -> Index (may be out of bounds) -> Result value): Border index (to treat indices near to bounds) |
| -> Dim2Stencil sx sy a b c | Convolution stencil |
| -> UArray r SH Dim2 a | Source array |
| -> UArray CV CVL Dim2 c | Fused convolved result array |
dConvolveLinearDim2WithStaticStencilSource
Arguments
| :: (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r L Dim2 a) | |
| => Dim2Stencil sx sy a b c | Convolution stencil |
| -> UArray r L Dim2 a | Source array |
| -> UArray CV CVL Dim2 c | Fused convolved result array |
Analog of dConvolveShDim2WithStaticStencil
to convolve arrays with Linear load index.
convolveLinearDim2WithStaticStencilSource
Arguments
| :: forall r sx sox eox sy soy eoy a b c . (StencilOffsets sx sox eox, StencilOffsets sy soy eoy, USource r L Dim2 a) | |
| => (UArray r L Dim2 a -> Dim2 -> Dim2 -> IO a) | (Source array -> Extent of this array -> Index (may be out of bounds) -> Result value): Border index (to treat indices near to bounds) |
| -> Dim2Stencil sx sy a b c | Convolution stencil |
| -> UArray r L Dim2 a | Source array |
| -> UArray CV CVL Dim2 c | Fused convolved result array |
Analog of convolveShDim2WithStaticStencil
to convolve arrays with Linear load index.