massiv-1.0.0.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2021
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Stencil

Description

 
Synopsis

Stencil

data Stencil ix e a Source #

Stencil is abstract description of how to handle elements in the neighborhood of every array cell in order to compute a value for the cells in the new array. Use makeStencil and makeConvolutionStencil in order to create a stencil.

Instances

Instances details
Functor (Stencil ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

fmap :: (a -> b) -> Stencil ix e a -> Stencil ix e b #

(<$) :: a -> Stencil ix e b -> Stencil ix e a #

Index ix => Applicative (Stencil ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

pure :: a -> Stencil ix e a #

(<*>) :: Stencil ix e (a -> b) -> Stencil ix e a -> Stencil ix e b #

liftA2 :: (a -> b -> c) -> Stencil ix e a -> Stencil ix e b -> Stencil ix e c #

(*>) :: Stencil ix e a -> Stencil ix e b -> Stencil ix e b #

(<*) :: Stencil ix e a -> Stencil ix e b -> Stencil ix e a #

(Index ix, Floating a) => Floating (Stencil ix e a) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

pi :: Stencil ix e a #

exp :: Stencil ix e a -> Stencil ix e a #

log :: Stencil ix e a -> Stencil ix e a #

sqrt :: Stencil ix e a -> Stencil ix e a #

(**) :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

logBase :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

sin :: Stencil ix e a -> Stencil ix e a #

cos :: Stencil ix e a -> Stencil ix e a #

tan :: Stencil ix e a -> Stencil ix e a #

asin :: Stencil ix e a -> Stencil ix e a #

acos :: Stencil ix e a -> Stencil ix e a #

atan :: Stencil ix e a -> Stencil ix e a #

sinh :: Stencil ix e a -> Stencil ix e a #

cosh :: Stencil ix e a -> Stencil ix e a #

tanh :: Stencil ix e a -> Stencil ix e a #

asinh :: Stencil ix e a -> Stencil ix e a #

acosh :: Stencil ix e a -> Stencil ix e a #

atanh :: Stencil ix e a -> Stencil ix e a #

log1p :: Stencil ix e a -> Stencil ix e a #

expm1 :: Stencil ix e a -> Stencil ix e a #

log1pexp :: Stencil ix e a -> Stencil ix e a #

log1mexp :: Stencil ix e a -> Stencil ix e a #

(Index ix, Fractional a) => Fractional (Stencil ix e a) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

(/) :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

recip :: Stencil ix e a -> Stencil ix e a #

fromRational :: Rational -> Stencil ix e a #

(Index ix, Num a) => Num (Stencil ix e a) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

(+) :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

(-) :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

(*) :: Stencil ix e a -> Stencil ix e a -> Stencil ix e a #

negate :: Stencil ix e a -> Stencil ix e a #

abs :: Stencil ix e a -> Stencil ix e a #

signum :: Stencil ix e a -> Stencil ix e a #

fromInteger :: Integer -> Stencil ix e a #

Index ix => NFData (Stencil ix e a) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

rnf :: Stencil ix e a -> () #

makeStencil Source #

Arguments

:: Index ix 
=> Sz ix

Size of the stencil

-> ix

Center of the stencil

-> ((ix -> e) -> a)

Stencil function that receives a "get" function as it's argument that can retrieve values of cells in the source array with respect to the center of the stencil. Stencil function must return a value that will be assigned to the cell in the result array. Offset supplied to the "get" function cannot go outside the boundaries of the stencil, otherwise an error will be raised during stencil creation.

-> Stencil ix e a 

Construct a stencil from a function, which describes how to calculate the value at a point while having access to neighboring elements with a function that accepts idices relative to the center of stencil. Trying to index outside the stencil box will result in a runtime error upon stencil creation.

Note - Once correctness of stencil is verified then switching to makeUnsafeStencil is recommended in order to get the most performance out of the Stencil

Example

Expand

Below is an example of creating a Stencil, which, when mapped over a 2-dimensional array, will compute an average of all elements in a 3x3 square for each element in that array.

Note - Make sure to add an INLINE pragma, otherwise performance will be terrible.

average3x3Stencil :: Fractional a => Stencil Ix2 a a
average3x3Stencil = makeStencil (Sz (3 :. 3)) (1 :. 1) $ \ get ->
  (  get (-1 :. -1) + get (-1 :. 0) + get (-1 :. 1) +
     get ( 0 :. -1) + get ( 0 :. 0) + get ( 0 :. 1) +
     get ( 1 :. -1) + get ( 1 :. 0) + get ( 1 :. 1)   ) / 9
{-# INLINE average3x3Stencil #-}

Since: 0.1.0

getStencilSize :: Stencil ix e a -> Sz ix Source #

Get the size of the stencil

Since: 0.4.3

getStencilCenter :: Stencil ix e a -> ix Source #

Get the index of the stencil's center

Since: 0.4.3

Padding

data Padding ix e Source #

Padding of the source array before stencil application.

Examples

Expand

In order to see the affect of padding we can simply apply an identity stencil to an array:

>>> import Data.Massiv.Array as A
>>> a = computeAs P $ resize' (Sz2 2 3) (Ix1 1 ... 6)
>>> applyStencil noPadding idStencil a
Array DW Seq (Sz (2 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  ]
>>> applyStencil (Padding (Sz2 1 2) (Sz2 3 4) (Fill 0)) idStencil a
Array DW Seq (Sz (6 :. 9))
  [ [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 1, 2, 3, 0, 0, 0, 0 ]
  , [ 0, 0, 4, 5, 6, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  ]

It is also a nice technique to see the border resolution strategy in action:

>>> applyStencil (Padding (Sz2 2 3) (Sz2 2 3) Wrap) idStencil a
Array DW Seq (Sz (6 :. 9))
  [ [ 1, 2, 3, 1, 2, 3, 1, 2, 3 ]
  , [ 4, 5, 6, 4, 5, 6, 4, 5, 6 ]
  , [ 1, 2, 3, 1, 2, 3, 1, 2, 3 ]
  , [ 4, 5, 6, 4, 5, 6, 4, 5, 6 ]
  , [ 1, 2, 3, 1, 2, 3, 1, 2, 3 ]
  , [ 4, 5, 6, 4, 5, 6, 4, 5, 6 ]
  ]
>>> applyStencil (Padding (Sz2 2 3) (Sz2 2 3) Edge) idStencil a
Array DW Seq (Sz (6 :. 9))
  [ [ 1, 1, 1, 1, 2, 3, 3, 3, 3 ]
  , [ 1, 1, 1, 1, 2, 3, 3, 3, 3 ]
  , [ 1, 1, 1, 1, 2, 3, 3, 3, 3 ]
  , [ 4, 4, 4, 4, 5, 6, 6, 6, 6 ]
  , [ 4, 4, 4, 4, 5, 6, 6, 6, 6 ]
  , [ 4, 4, 4, 4, 5, 6, 6, 6, 6 ]
  ]
>>> applyStencil (Padding (Sz2 2 3) (Sz2 2 3) Reflect) idStencil a
Array DW Seq (Sz (6 :. 9))
  [ [ 6, 5, 4, 4, 5, 6, 6, 5, 4 ]
  , [ 3, 2, 1, 1, 2, 3, 3, 2, 1 ]
  , [ 3, 2, 1, 1, 2, 3, 3, 2, 1 ]
  , [ 6, 5, 4, 4, 5, 6, 6, 5, 4 ]
  , [ 6, 5, 4, 4, 5, 6, 6, 5, 4 ]
  , [ 3, 2, 1, 1, 2, 3, 3, 2, 1 ]
  ]
>>> applyStencil (Padding (Sz2 2 3) (Sz2 2 3) Continue) idStencil a
Array DW Seq (Sz (6 :. 9))
  [ [ 1, 3, 2, 1, 2, 3, 2, 1, 3 ]
  , [ 4, 6, 5, 4, 5, 6, 5, 4, 6 ]
  , [ 1, 3, 2, 1, 2, 3, 2, 1, 3 ]
  , [ 4, 6, 5, 4, 5, 6, 5, 4, 6 ]
  , [ 1, 3, 2, 1, 2, 3, 2, 1, 3 ]
  , [ 4, 6, 5, 4, 5, 6, 5, 4, 6 ]
  ]

Since: 0.4.3

Constructors

Padding 

Fields

Instances

Instances details
(Eq ix, Eq e) => Eq (Padding ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil

Methods

(==) :: Padding ix e -> Padding ix e -> Bool #

(/=) :: Padding ix e -> Padding ix e -> Bool #

(Index ix, Show e) => Show (Padding ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil

Methods

showsPrec :: Int -> Padding ix e -> ShowS #

show :: Padding ix e -> String #

showList :: [Padding ix e] -> ShowS #

noPadding :: Index ix => Padding ix e Source #

Also known as "valid" padding. When stencil is applied to an array, that array will shrink, unless the stencil is of size 1.

Since: 0.4.3

samePadding :: Index ix => Stencil ix e a -> Border e -> Padding ix e Source #

Padding that matches the size of the stencil, which is known as "same" padding, because when a stencil is applied to an array with such matching padding, the resulting array will be of the same size as the source array. This is exactly the behavior of mapStencil

Since: 0.4.3

Application

mapStencil Source #

Arguments

:: (Index ix, Manifest r e) 
=> Border e

Border resolution technique

-> Stencil ix e a

Stencil to map over the array

-> Array r ix e

Source array

-> Array DW ix a 

Map a constructed stencil over an array. Resulting array must be computed in order to be useful.

Since: 0.1.0

applyStencil Source #

Arguments

:: (Index ix, Manifest r e) 
=> Padding ix e

Padding to be applied to the source array. This will dictate the resulting size of the array. No padding will cause it to shrink by the size of the stencil

-> Stencil ix e a

Stencil to apply to the array

-> Array r ix e

Source array

-> Array DW ix a 

Apply a constructed stencil over an array. Resulting array must be computed in order to be useful. Unlike mapStencil, the size of the resulting array will not necesserally be the same as the source array, which will depend on the padding.

Since: 0.4.3

Common stencils

idStencil :: Index ix => Stencil ix e e Source #

Identity stencil that does not change the elements of the source array.

Since: 0.4.3

sumStencil :: (Num e, Index ix) => Sz ix -> Stencil ix e e Source #

Sum all elements in the stencil region

Examples

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs P $ iterateN (Sz2 2 5) (* 2) (1 :: Int)
>>> a
Array P Seq (Sz (2 :. 5))
  [ [ 2, 4, 8, 16, 32 ]
  , [ 64, 128, 256, 512, 1024 ]
  ]
>>> applyStencil noPadding (sumStencil (Sz2 1 2)) a
Array DW Seq (Sz (2 :. 4))
  [ [ 6, 12, 24, 48 ]
  , [ 192, 384, 768, 1536 ]
  ]
>>> [2 + 4, 4 + 8, 8 + 16, 16 + 32] :: [Int]
[6,12,24,48]

Since: 0.4.3

productStencil :: (Num e, Index ix) => Sz ix -> Stencil ix e e Source #

Multiply all elements in the stencil region

Examples

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs P $ iterateN (Sz2 2 2) (+1) (0 :: Int)
>>> a
Array P Seq (Sz (2 :. 2))
  [ [ 1, 2 ]
  , [ 3, 4 ]
  ]
>>> applyStencil (Padding 0 2 (Fill 0)) (productStencil 2) a
Array DW Seq (Sz (3 :. 3))
  [ [ 24, 0, 0 ]
  , [ 0, 0, 0 ]
  , [ 0, 0, 0 ]
  ]
>>> applyStencil (Padding 0 2 Reflect) (productStencil 2) a
Array DW Seq (Sz (3 :. 3))
  [ [ 24, 64, 24 ]
  , [ 144, 256, 144 ]
  , [ 24, 64, 24 ]
  ]

Since: 0.4.3

avgStencil :: (Fractional e, Index ix) => Sz ix -> Stencil ix e e Source #

Find the average value of all elements in the stencil region

Example

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs P $ iterateN (Sz2 3 4) (+1) (10 :: Double)
>>> a
Array P Seq (Sz (3 :. 4))
  [ [ 11.0, 12.0, 13.0, 14.0 ]
  , [ 15.0, 16.0, 17.0, 18.0 ]
  , [ 19.0, 20.0, 21.0, 22.0 ]
  ]
>>> applyStencil noPadding (avgStencil (Sz2 2 3)) a
Array DW Seq (Sz (2 :. 2))
  [ [ 14.0, 15.0 ]
  , [ 18.0, 19.0 ]
  ]
>>> Prelude.sum [11.0, 12.0, 13.0, 15.0, 16.0, 17.0] / 6 :: Double
14.0

Since: 0.4.3

maxStencil :: (Bounded e, Ord e, Index ix) => Sz ix -> Stencil ix e e Source #

Create a stencil centered at 0 that will extract the maximum value in the region of supplied size.

Example

Expand

Here is a sample implementation of max pooling.

>>> import Data.Massiv.Array as A
>>> a <- computeAs P <$> resizeM (Sz2 9 9) (Ix1 10 ..: 91)
>>> a
Array P Seq (Sz (9 :. 9))
  [ [ 10, 11, 12, 13, 14, 15, 16, 17, 18 ]
  , [ 19, 20, 21, 22, 23, 24, 25, 26, 27 ]
  , [ 28, 29, 30, 31, 32, 33, 34, 35, 36 ]
  , [ 37, 38, 39, 40, 41, 42, 43, 44, 45 ]
  , [ 46, 47, 48, 49, 50, 51, 52, 53, 54 ]
  , [ 55, 56, 57, 58, 59, 60, 61, 62, 63 ]
  , [ 64, 65, 66, 67, 68, 69, 70, 71, 72 ]
  , [ 73, 74, 75, 76, 77, 78, 79, 80, 81 ]
  , [ 82, 83, 84, 85, 86, 87, 88, 89, 90 ]
  ]
>>> computeWithStrideAs P (Stride 3) $ mapStencil Edge (maxStencil (Sz 3)) a
Array P Seq (Sz (3 :. 3))
  [ [ 30, 33, 36 ]
  , [ 57, 60, 63 ]
  , [ 84, 87, 90 ]
  ]

Since: 0.4.3

minStencil :: (Bounded e, Ord e, Index ix) => Sz ix -> Stencil ix e e Source #

Create a stencil centered at 0 that will extract the maximum value in the region of supplied size.

Example

Expand

Here is a sample implementation of min pooling.

>>> import Data.Massiv.Array as A
>>> a <- computeAs P <$> resizeM (Sz2 9 9) (Ix1 10 ..: 91)
>>> a
Array P Seq (Sz (9 :. 9))
  [ [ 10, 11, 12, 13, 14, 15, 16, 17, 18 ]
  , [ 19, 20, 21, 22, 23, 24, 25, 26, 27 ]
  , [ 28, 29, 30, 31, 32, 33, 34, 35, 36 ]
  , [ 37, 38, 39, 40, 41, 42, 43, 44, 45 ]
  , [ 46, 47, 48, 49, 50, 51, 52, 53, 54 ]
  , [ 55, 56, 57, 58, 59, 60, 61, 62, 63 ]
  , [ 64, 65, 66, 67, 68, 69, 70, 71, 72 ]
  , [ 73, 74, 75, 76, 77, 78, 79, 80, 81 ]
  , [ 82, 83, 84, 85, 86, 87, 88, 89, 90 ]
  ]
>>> computeWithStrideAs P (Stride 3) $ mapStencil Edge (minStencil (Sz 3)) a
Array P Seq (Sz (3 :. 3))
  [ [ 10, 13, 16 ]
  , [ 37, 40, 43 ]
  , [ 64, 67, 70 ]
  ]

Since: 0.4.3

foldlStencil :: Index ix => (a -> e -> a) -> a -> Sz ix -> Stencil ix e a Source #

Stencil that does a left fold in a row-major order. Regardless of the supplied size resulting stencil will be centered at zero, although by using Padding it is possible to overcome this limitation.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs P $ iterateN (Sz2 3 4) (+1) (10 :: Int)
>>> a
Array P Seq (Sz (3 :. 4))
  [ [ 11, 12, 13, 14 ]
  , [ 15, 16, 17, 18 ]
  , [ 19, 20, 21, 22 ]
  ]
>>> applyStencil noPadding (foldlStencil (flip (:)) [] (Sz2 3 2)) a
Array DW Seq (Sz (1 :. 3))
  [ [ [20,19,16,15,12,11], [21,20,17,16,13,12], [22,21,18,17,14,13] ]
  ]
>>> applyStencil (Padding (Sz2 1 0) 0 (Fill 10)) (foldlStencil (flip (:)) [] (Sz2 3 2)) a
Array DW Seq (Sz (2 :. 3))
  [ [ [16,15,12,11,10,10], [17,16,13,12,10,10], [18,17,14,13,10,10] ]
  , [ [20,19,16,15,12,11], [21,20,17,16,13,12], [22,21,18,17,14,13] ]
  ]

Since: 0.4.3

foldrStencil :: Index ix => (e -> a -> a) -> a -> Sz ix -> Stencil ix e a Source #

Stencil that does a right fold in a row-major order. Regardless of the supplied size resulting stencil will be centered at zero, although by using Padding it is possible to overcome this limitation.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs P $ iterateN (Sz2 3 4) (+1) (10 :: Int)
>>> a
Array P Seq (Sz (3 :. 4))
  [ [ 11, 12, 13, 14 ]
  , [ 15, 16, 17, 18 ]
  , [ 19, 20, 21, 22 ]
  ]
>>> applyStencil noPadding (foldrStencil (:) [] (Sz2 2 3)) a
Array DW Seq (Sz (2 :. 2))
  [ [ [11,12,13,15,16,17], [12,13,14,16,17,18] ]
  , [ [15,16,17,19,20,21], [16,17,18,20,21,22] ]
  ]

Since: 0.4.3

foldStencil :: (Monoid e, Index ix) => Sz ix -> Stencil ix e e Source #

Create a stencil that will fold all elements in the region monoidally.

Since: 0.4.3

Profunctor

dimapStencil :: (c -> d) -> (a -> b) -> Stencil ix d a -> Stencil ix c b Source #

A Profunctor dimap. Same caviat applies as in lmapStencil

Since: 0.2.3

lmapStencil :: (c -> d) -> Stencil ix d a -> Stencil ix c a Source #

A contravariant map of a second type parameter. In other words map a function over each element of the array, that the stencil will be applied to.

Note: This map can be very inefficient, since for stencils larger than 1 element in size, the supllied function will be repeatedly applied to the same element. It is better to simply map that function over the source array instead.

Since: 0.2.3

rmapStencil :: (a -> b) -> Stencil ix e a -> Stencil ix e b Source #

A covariant map over the right most type argument. In other words the usual fmap from Functor:

fmap == rmapStencil

Since: 0.2.3

Convolution

makeConvolutionStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #

Create a convolution stencil by specifying border resolution technique and an accumulator function.

Note - Using makeUnsafeConvolutionStencil will be much faster, therefore it is recommended to switch from this function, after manual verification that the created stencil behaves as expected.

Examples

Expand

Here is how to create a 2D horizontal Sobel Stencil:

sobelX :: Num e => Stencil Ix2 e e
sobelX = makeConvolutionStencil (Sz2 3 3) (1 :. 1) $
           \f -> f (-1 :. -1) (-1) . f (-1 :. 1) 1 .
                 f ( 0 :. -1) (-2) . f ( 0 :. 1) 2 .
                 f ( 1 :. -1) (-1) . f ( 1 :. 1) 1
{-# INLINE sobelX #-}

Since: 0.1.0

makeConvolutionStencilFromKernel :: (Manifest r e, Index ix, Num e) => Array r ix e -> Stencil ix e e Source #

Make a stencil out of a Kernel Array. This Stencil will be slower than if makeConvolutionStencil is used, but sometimes we just really don't know the kernel at compile time.

Since: 0.1.0

makeCorrelationStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #

Make a cross-correlation stencil

Note - Using makeUnsafeCorrelationStencil will be much faster, therefore it is recommended to switch from this function, after manual verification that the created stencil behaves as expected.

Since: 0.1.5

makeCorrelationStencilFromKernel :: (Manifest r e, Index ix, Num e) => Array r ix e -> Stencil ix e e Source #

Make a cross-correlation stencil out of a Kernel Array. This Stencil will be slower than if makeCorrelationStencil is used, but sometimes we just really don't know the kernel at compile time.

Since: 0.1.5