friday-0.1.5: A functionnal image processing library for Haskell.

Safe HaskellNone

Vision.Image.Filter

Contents

Description

Provides high level functions to define and apply filters on images.

Filters are operations on images on which the surrounding of each processed pixel is considered according to a kernel.

See http://en.wikipedia.org/wiki/Kernel_(image_processing) for details.

The radius argument of some filters is used to determine the kernel size. A radius as of 1 means a kernel of size 3, 2 a kernel of size 5 and so on.

The acc type argument of some filters defines the type which will be used to store the accumulated value of the kernel (e.g. by setting acc to Double in the computation of a Gaussian blur, the kernel average will be computed using a Double).

To apply a filter to an image, use the apply method:

 let filter :: SeparableFilter GreyPixel Double GreyPixel
     filter = gaussianBlur 2 Nothing
 in apply filter img :: Grey

Synopsis

Types

class Filterable src res f whereSource

Provides an implementation to execute a type of filter.

src is the original image, res the resulting image and f the filter.

Methods

apply :: f -> src -> resSource

Applies the given filter on the given image.

Instances

(Image src, FromFunction res, SeparatelyFiltrable src res src_p, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res src_p), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res src_p)) src_p, Image (SeparableFilterAccumulator src res src_p), ~ * (ImagePixel (SeparableFilterAccumulator src res src_p)) src_p) => Filterable src res (SeparableFilter1 src_p res_p)

Separable filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_p res_p)

Box filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, SeparatelyFiltrable src res acc, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res acc), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res acc)) acc, Image (SeparableFilterAccumulator src res acc), ~ * (ImagePixel (SeparableFilterAccumulator src res acc)) acc) => Filterable src res (SeparableFilter src_p acc res_p)

Separable filters initialized with a given value.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter src_p acc res_p)

Box filters initialized with a given value.

data Filter src kernel init acc res Source

Constructors

Filter 

Fields

fKernelSize :: !Size
 
fKernelCenter :: !KernelAnchor
 
fKernel :: !kernel

See Kernel and SeparableKernel.

fInit :: !init

Defines how the accumulated value is initialized.

See FilterFold and FilterFold1.

fPost :: !(src -> acc -> res)
 
fInterpol :: !(BorderInterpolate src)
 

Instances

(Image src, FromFunction res, SeparatelyFiltrable src res src_p, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res src_p), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res src_p)) src_p, Image (SeparableFilterAccumulator src res src_p), ~ * (ImagePixel (SeparableFilterAccumulator src res src_p)) src_p) => Filterable src res (SeparableFilter1 src_p res_p)

Separable filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_p res_p)

Box filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, SeparatelyFiltrable src res acc, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res acc), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res acc)) acc, Image (SeparableFilterAccumulator src res acc), ~ * (ImagePixel (SeparableFilterAccumulator src res acc)) acc) => Filterable src res (SeparableFilter src_p acc res_p)

Separable filters initialized with a given value.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter src_p acc res_p)

Box filters initialized with a given value.

type BoxFilter src acc res = Filter src (Kernel src acc) (FilterFold acc) acc resSource

2D filters which are initialized with a value.

type BoxFilter1 src res = Filter src (Kernel src src) FilterFold1 src resSource

2D filters which are not initialized with a value.

type SeparableFilter src acc res = Filter src (SeparableKernel src acc) (FilterFold acc) acc resSource

Separable 2D filters which are initialized with a value.

type SeparableFilter1 src res = Filter src (SeparableKernel src src) FilterFold1 src resSource

Separable 2D filters which are not initialized with a value.

data KernelAnchor Source

Defines how the center of the kernel will be determined.

newtype Kernel src acc Source

A simple 2D kernel.

The kernel function accepts the coordinates in the kernel, the value of the pixel at these coordinates (src), the current accumulated value and returns a new accumulated value.

Non-separable filters computational complexity grows quadratically according to the size of the sides of the kernel.

Constructors

Kernel (DIM2 -> src -> acc -> acc) 

Instances

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_p res_p)

Box filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter src_p acc res_p)

Box filters initialized with a given value.

data SeparableKernel src acc Source

Some kernels can be factorized in two uni-dimensional kernels (horizontal and vertical).

Separable filters computational complexity grows linearly according to the size of the sides of the kernel.

See http://http://en.wikipedia.org/wiki/Separable_filter.

Constructors

SeparableKernel 

Fields

skVertical :: !(DIM1 -> src -> acc -> acc)

Vertical (column) kernel.

skHorizontal :: !(DIM1 -> acc -> acc -> acc)

Horizontal (row) kernel.

Instances

(Image src, FromFunction res, SeparatelyFiltrable src res src_p, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res src_p), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res src_p)) src_p, Image (SeparableFilterAccumulator src res src_p), ~ * (ImagePixel (SeparableFilterAccumulator src res src_p)) src_p) => Filterable src res (SeparableFilter1 src_p res_p)

Separable filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, SeparatelyFiltrable src res acc, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res acc), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res acc)) acc, Image (SeparableFilterAccumulator src res acc), ~ * (ImagePixel (SeparableFilterAccumulator src res acc)) acc) => Filterable src res (SeparableFilter src_p acc res_p)

Separable filters initialized with a given value.

class SeparatelyFiltrable src res acc Source

Used to determine the type of the accumulator image used when computing separable filters.

src and res are respectively the source and the result image types while acc is the pixel type of the accumulator.

Associated Types

type SeparableFilterAccumulator src res acc Source

Instances

data FilterFold acc Source

Uses an initial value to initialize the filter.

Constructors

FilterFold acc 

Instances

(Image src, FromFunction res, SeparatelyFiltrable src res acc, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res acc), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res acc)) acc, Image (SeparableFilterAccumulator src res acc), ~ * (ImagePixel (SeparableFilterAccumulator src res acc)) acc) => Filterable src res (SeparableFilter src_p acc res_p)

Separable filters initialized with a given value.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter src_p acc res_p)

Box filters initialized with a given value.

data FilterFold1 Source

Uses the first pixel in the kernel as initial value. The kernel must not be empty and the accumulator type must be the same as the source pixel type.

This kind of initialization is needed by morphological filters.

Constructors

FilterFold1 

Instances

(Image src, FromFunction res, SeparatelyFiltrable src res src_p, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res), FromFunction (SeparableFilterAccumulator src res src_p), ~ * (FromFunctionPixel (SeparableFilterAccumulator src res src_p)) src_p, Image (SeparableFilterAccumulator src res src_p), ~ * (ImagePixel (SeparableFilterAccumulator src res src_p)) src_p) => Filterable src res (SeparableFilter1 src_p res_p)

Separable filters initialized using the first pixel of the kernel.

(Image src, FromFunction res, ~ * src_p (ImagePixel src), ~ * res_p (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_p res_p)

Box filters initialized using the first pixel of the kernel.

data BorderInterpolate a Source

Defines how image boundaries are extrapolated by the algorithms.

'|' characters in examples are image borders.

Constructors

BorderReplicate

Replicates the first and last pixels of the image.

 aaaaaa|abcdefgh|hhhhhhh
BorderReflect

Reflects the border of the image.

 fedcba|abcdefgh|hgfedcb
BorderWrap

Considers that the last pixel of the image is before the first one.

 cdefgh|abcdefgh|abcdefg
BorderConstant !a

Assigns a constant value to out of image pixels.

 iiiiii|abcdefgh|iiiiiii  with some specified 'i'

Functions

kernelAnchor :: KernelAnchor -> Size -> DIM2Source

Given a method to compute the kernel anchor and the size of the kernel, returns the anchor of the kernel as coordinates.

borderInterpolateSource

Arguments

:: BorderInterpolate a 
-> Int

The size of the dimension.

-> Int

The index in the dimension.

-> Either Int a 

Given a method of interpolation, the number of pixel in the dimension and an index in this dimension, returns either the index of the interpolated pixel or a constant value.

Filters

Morphological operators

dilate :: Ord src => Int -> SeparableFilter1 src srcSource

erode :: Ord src => Int -> SeparableFilter1 src srcSource

Blur

blurSource

Arguments

:: (Integral src, Integral acc, Num res) 
=> Int

Blur radius.

-> SeparableFilter src acc res 

Blurs the image by averaging the pixel inside the kernel.

Considers using a type for acc with maxBound acc >= maxBound src * (kernel size).

gaussianBlurSource

Arguments

:: (Integral src, Floating acc, RealFrac acc, Storable acc, Integral res) 
=> Int

Blur radius.

-> Maybe acc

Sigma value of the Gaussian function. If not given, will be automatically computed from the radius so that the kernel fits 3σ of the distribution.

-> SeparableFilter src acc res 

Blurs the image by averaging the pixel inside the kernel using a Gaussian function.

See http://en.wikipedia.org/wiki/Gaussian_blur

Derivation

scharr :: (Integral src, Integral res) => Derivative -> SeparableFilter src res resSource

Estimates the first derivative using the Scharr's 3x3 kernel.

Convolves the following kernel for the X derivative:

  -3   0   3
 -10   0  10
  -3   0   3

And this kernel for the Y derivative:

  -3 -10  -3
   0   0   0
   3  10   3

Considers using a signed integer type for res with maxBound res >= 16 * maxBound src.

sobelSource

Arguments

:: (Integral src, Integral res, Storable res) 
=> Int

Kernel radius.

-> Derivative 
-> SeparableFilter src res res 

Estimates the first derivative using a Sobel's kernel.

Prefer scharr when radius equals 1 as Scharr's kernel is more accurate and is implemented faster.

Considers using a signed integer type for res which is significantly larger than src, especially for large kernels.