friday-0.2.3.1: A functional image processing library for Haskell.

Safe HaskellNone
LanguageHaskell2010

Vision.Image.Filter.Internal

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.

Please use Filter if you only want to apply filter to images.

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

let -- Creates a filter which will blur the image. Uses a Double as
    -- accumulator of the Gaussian kernel.
    filter :: Blur GreyPixel Double GreyPixel
    filter = gaussianBlur 2 Nothing
in apply filter img :: Grey

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).

Synopsis

Types

class Filterable src res f where Source #

Provides an implementation to execute a type of filter.

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

Minimal complete definition

apply

Methods

apply :: f -> src -> res Source #

Applies the given filter on the given image.

Instances

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res src_pix) => Filterable src res (SeparableFilter1 src_pix init res_pix) Source #

Separable filters initialized using the first pixel of the kernel.

Methods

apply :: SeparableFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_pix init res_pix) Source #

Box filters initialized using the first pixel of the kernel.

Methods

apply :: BoxFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res acc) => Filterable src res (SeparableFilter src_pix init acc res_pix) Source #

Separable filters initialized with a given value.

Methods

apply :: SeparableFilter src_pix init acc res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter src_pix init acc res_pix) Source #

Box filters initialized with a given value.

Methods

apply :: BoxFilter src_pix init acc res_pix -> src -> res Source #

data Filter src kernel init fold acc res Source #

Constructors

Filter 

Fields

Instances

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res src_pix) => Filterable src res (SeparableFilter1 src_pix init res_pix) Source #

Separable filters initialized using the first pixel of the kernel.

Methods

apply :: SeparableFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_pix init res_pix) Source #

Box filters initialized using the first pixel of the kernel.

Methods

apply :: BoxFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res acc) => Filterable src res (SeparableFilter src_pix init acc res_pix) Source #

Separable filters initialized with a given value.

Methods

apply :: SeparableFilter src_pix init acc res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter src_pix init acc res_pix) Source #

Box filters initialized with a given value.

Methods

apply :: BoxFilter src_pix init acc res_pix -> src -> res Source #

type BoxFilter src init acc res = Filter src (Kernel src init acc) init (FilterFold acc) acc res Source #

2D filters which are initialized with a value.

type BoxFilter1 src init res = Filter src (Kernel src init src) init FilterFold1 src res Source #

2D filters which are not initialized with a value.

type SeparableFilter src init acc res = Filter src (SeparableKernel src init acc) init (FilterFold acc) acc res Source #

Separable 2D filters which are initialized with a value.

type SeparableFilter1 src init res = Filter src (SeparableKernel src init src) init FilterFold1 src res Source #

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 init 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 (init -> Point -> src -> acc -> acc) 

Instances

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_pix init res_pix) Source #

Box filters initialized using the first pixel of the kernel.

Methods

apply :: BoxFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter src_pix init acc res_pix) Source #

Box filters initialized with a given value.

Methods

apply :: BoxFilter src_pix init acc res_pix -> src -> res Source #

data SeparableKernel src init 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 :: !(init -> DIM1 -> src -> acc -> acc)

    Vertical (column) kernel.

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

    Horizontal (row) kernel.

Instances

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res src_pix) => Filterable src res (SeparableFilter1 src_pix init res_pix) Source #

Separable filters initialized using the first pixel of the kernel.

Methods

apply :: SeparableFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res acc) => Filterable src res (SeparableFilter src_pix init acc res_pix) Source #

Separable filters initialized with a given value.

Methods

apply :: SeparableFilter src_pix init acc res_pix -> src -> res Source #

class (Image (SeparableFilterAccumulator src res acc), ImagePixel (SeparableFilterAccumulator src res acc) ~ acc, FromFunction (SeparableFilterAccumulator src res acc), FromFunctionPixel (SeparableFilterAccumulator src res acc) ~ acc) => 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

Storable acc => SeparatelyFiltrable src (Delayed p) acc Source # 

Associated Types

type SeparableFilterAccumulator src (Delayed p) acc :: * Source #

Storable acc => SeparatelyFiltrable src (Manifest p) acc Source # 

Associated Types

type SeparableFilterAccumulator src (Manifest p) acc :: * Source #

data FilterFold acc Source #

Uses the result of the provided function as the initial value of the kernel's accumulator, depending on the center coordinates in the image.

For most filters, the function will always return the same value (i.e. defined as const 0), but this kind of initialization could be required for some filters.

Constructors

FilterFold (Point -> acc) 

Instances

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res acc) => Filterable src res (SeparableFilter src_pix init acc res_pix) Source #

Separable filters initialized with a given value.

Methods

apply :: SeparableFilter src_pix init acc res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter src_pix init acc res_pix) Source #

Box filters initialized with a given value.

Methods

apply :: BoxFilter src_pix init acc res_pix -> src -> res Source #

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, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res), SeparatelyFiltrable src res src_pix) => Filterable src res (SeparableFilter1 src_pix init res_pix) Source #

Separable filters initialized using the first pixel of the kernel.

Methods

apply :: SeparableFilter1 src_pix init res_pix -> src -> res Source #

(Image src, FromFunction res, (~) * src_pix (ImagePixel src), (~) * res_pix (FromFunctionPixel res)) => Filterable src res (BoxFilter1 src_pix init res_pix) Source #

Box filters initialized using the first pixel of the kernel.

Methods

apply :: BoxFilter1 src_pix init res_pix -> src -> res Source #

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 -> Point Source #

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

borderInterpolate Source #

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

type Morphological pix = SeparableFilter1 pix () pix Source #

dilate :: Ord pix => Int -> Morphological pix Source #

erode :: Ord pix => Int -> Morphological pix Source #

Blur

type Blur src acc res = SeparableFilter src () acc res Source #

blur Source #

Arguments

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

Blur radius.

-> Blur 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)².

gaussianBlur Source #

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.

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

type Derivative src res = SeparableFilter src () res res Source #

scharr :: (Integral src, Integral res) => DerivativeType -> Derivative src res Source #

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.

sobel Source #

Arguments

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

Kernel radius.

-> DerivativeType 
-> Derivative src 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.

Others

type Mean src acc res = SeparableFilter src () acc res Source #

mean :: (Integral src, Integral acc, Fractional res) => Size -> SeparableFilter src () acc res Source #

Computes the average of a kernel of the given size.

This is similar to blur but with a rectangular kernel and a Fractional result.