massiv-0.2.5.0: Massiv (Массив) is an Array Library.

Copyright(c) Alexey Kuleshevich 2018
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Stencil

Contents

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
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 -> () #

data Value e Source #

This is a simple wrapper for value of an array cell. It is used in order to improve safety of Stencil mapping. Using various class instances, such as Num and Functor for example, make it possible to manipulate the value, without having direct access to it.

Instances
Functor Value Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Applicative Value Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

pure :: a -> Value a #

(<*>) :: Value (a -> b) -> Value a -> Value b #

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

(*>) :: Value a -> Value b -> Value b #

(<*) :: Value a -> Value b -> Value a #

Bounded e => Bounded (Value e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

minBound :: Value e #

maxBound :: Value e #

Floating e => Floating (Value e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

pi :: Value e #

exp :: Value e -> Value e #

log :: Value e -> Value e #

sqrt :: Value e -> Value e #

(**) :: Value e -> Value e -> Value e #

logBase :: Value e -> Value e -> Value e #

sin :: Value e -> Value e #

cos :: Value e -> Value e #

tan :: Value e -> Value e #

asin :: Value e -> Value e #

acos :: Value e -> Value e #

atan :: Value e -> Value e #

sinh :: Value e -> Value e #

cosh :: Value e -> Value e #

tanh :: Value e -> Value e #

asinh :: Value e -> Value e #

acosh :: Value e -> Value e #

atanh :: Value e -> Value e #

log1p :: Value e -> Value e #

expm1 :: Value e -> Value e #

log1pexp :: Value e -> Value e #

log1mexp :: Value e -> Value e #

Fractional e => Fractional (Value e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

(/) :: Value e -> Value e -> Value e #

recip :: Value e -> Value e #

fromRational :: Rational -> Value e #

Num e => Num (Value e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

(+) :: Value e -> Value e -> Value e #

(-) :: Value e -> Value e -> Value e #

(*) :: Value e -> Value e -> Value e #

negate :: Value e -> Value e #

abs :: Value e -> Value e #

signum :: Value e -> Value e #

fromInteger :: Integer -> Value e #

Show e => Show (Value e) Source # 
Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

showsPrec :: Int -> Value e -> ShowS #

show :: Value e -> String #

showList :: [Value e] -> ShowS #

Semigroup a => Semigroup (Value a) Source #

Since: 0.1.5

Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

(<>) :: Value a -> Value a -> Value a #

sconcat :: NonEmpty (Value a) -> Value a #

stimes :: Integral b => b -> Value a -> Value a #

Monoid a => Monoid (Value a) Source #

Since: 0.1.5

Instance details

Defined in Data.Massiv.Array.Stencil.Internal

Methods

mempty :: Value a #

mappend :: Value a -> Value a -> Value a #

mconcat :: [Value a] -> Value a #

makeStencil Source #

Arguments

:: (Index ix, Default e) 
=> ix

Size of the stencil

-> ix

Center of the stencil

-> ((ix -> Value e) -> Value 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.

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 INLINE pragma, otherwise performance will be terrible.

average3x3Stencil :: (Default a, Fractional a) => Stencil Ix2 a a
average3x3Stencil = makeStencil (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 #-}

makeStencilDef Source #

Arguments

:: Index ix 
=> e 
-> ix

Size of the stencil

-> ix

Center of the stencil

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

Stencil function.

-> Stencil ix e a 

Same as makeStencil, but with ability to specify default value for stencil validation.

mapStencil Source #

Arguments

:: (Source r ix e, Manifest r ix 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.

Profunctor

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

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

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

Convolution

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

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

Examples

Expand

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

sobelX :: Num e => Stencil Ix2 e e
sobelX = makeConvolutionStencil (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 #-}

makeConvolutionStencilFromKernel :: (Manifest r ix e, 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.

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

Make a cross-correlation stencil.

makeCorrelationStencilFromKernel :: (Manifest r ix e, 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 makeCorrelationStencil is used, but sometimes we just really don't know the kernel at compile time.