Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Histogram sh a = Histogram {}
- class Shape sh => HistogramShape sh where
- toBin :: sh -> sh -> sh -> sh
- class (Pixel p, Shape (PixelValueSpace p)) => ToHistogram p where
- type PixelValueSpace p
- pixToIndex :: p -> PixelValueSpace p
- domainSize :: p -> PixelValueSpace p
- index :: (Shape sh, Storable a) => Histogram sh a -> sh -> a
- (!) :: (Shape sh, Storable a) => Histogram sh a -> sh -> a
- linearIndex :: (Shape sh, Storable a) => Histogram sh a -> Int -> a
- map :: (Storable a, Storable b) => (a -> b) -> Histogram sh a -> Histogram sh b
- assocs :: (Shape sh, Storable a) => Histogram sh a -> [(sh, a)]
- pixToBin :: (HistogramShape (PixelValueSpace p), ToHistogram p) => PixelValueSpace p -> p -> PixelValueSpace p
- histogram :: (MaskedImage i, ToHistogram (ImagePixel i), Storable a, Num a, HistogramShape (PixelValueSpace (ImagePixel i))) => Maybe (PixelValueSpace (ImagePixel i)) -> i -> Histogram (PixelValueSpace (ImagePixel i)) a
- histogram2D :: (Image i, ToHistogram (ImagePixel i), Storable a, Num a, HistogramShape (PixelValueSpace (ImagePixel i))) => ((PixelValueSpace (ImagePixel i) :. Int) :. Int) -> i -> Histogram ((PixelValueSpace (ImagePixel i) :. Int) :. Int) a
- reduce :: (HistogramShape sh, Storable a, Num a) => Histogram ((sh :. Int) :. Int) a -> Histogram sh a
- resize :: (HistogramShape sh, Storable a, Num a) => sh -> Histogram sh a -> Histogram sh a
- cumulative :: (Storable a, Num a) => Histogram DIM1 a -> Histogram DIM1 a
- normalize :: (Storable a, Real a, Storable b, Fractional b) => b -> Histogram sh a -> Histogram sh b
- equalizeImage :: (FunctorImage i i, Integral (ImagePixel i), ToHistogram (ImagePixel i), PixelValueSpace (ImagePixel i) ~ DIM1) => i -> i
- compareCorrel :: (Shape sh, Storable a, Real a, Storable b, Eq b, Floating b) => Histogram sh a -> Histogram sh a -> b
- compareChi :: (Shape sh, Storable a, Real a, Storable b, Fractional b) => Histogram sh a -> Histogram sh a -> b
- compareIntersect :: (Shape sh, Storable a, Num a, Ord a) => Histogram sh a -> Histogram sh a -> a
- compareEMD :: (Num a, Storable a) => Histogram DIM1 a -> Histogram DIM1 a -> a
Types & helpers
Instances
(Show sh, Show a, Storable a) => Show (Histogram sh a) Source # | |
(Storable a, Eq sh, Eq a) => Eq (Histogram sh a) Source # | |
(Storable a, Ord sh, Ord a) => Ord (Histogram sh a) Source # | |
Defined in Vision.Histogram compare :: Histogram sh a -> Histogram sh a -> Ordering # (<) :: Histogram sh a -> Histogram sh a -> Bool # (<=) :: Histogram sh a -> Histogram sh a -> Bool # (>) :: Histogram sh a -> Histogram sh a -> Bool # (>=) :: Histogram sh a -> Histogram sh a -> Bool # |
class Shape sh => HistogramShape sh where Source #
Subclass of Shape
which defines how to resize a shape so it will fit
inside a resized histogram.
:: sh | The number of bins we are mapping to. |
-> sh | The number of possible values of the original index. |
-> sh | The original index. |
-> sh | The index of the bin in the histogram. |
Given a number of bins of an histogram, reduces an index so it will be mapped to a bin.
class (Pixel p, Shape (PixelValueSpace p)) => ToHistogram p where Source #
This class defines how many dimensions a histogram will have and what will be the default number of bins.
type PixelValueSpace p Source #
pixToIndex :: p -> PixelValueSpace p Source #
Converts a pixel to an index.
domainSize :: p -> PixelValueSpace p Source #
Returns the maximum number of different values an index can take for
each dimension of the histogram (aka. the maximum index returned by
pixToIndex
plus one).
Instances
ToHistogram GreyPixel Source # | |
Defined in Vision.Histogram type PixelValueSpace GreyPixel Source # | |
ToHistogram HSVPixel Source # | |
Defined in Vision.Histogram type PixelValueSpace HSVPixel Source # | |
ToHistogram RGBPixel Source # | |
Defined in Vision.Histogram type PixelValueSpace RGBPixel Source # | |
ToHistogram RGBAPixel Source # | |
Defined in Vision.Histogram type PixelValueSpace RGBAPixel Source # |
linearIndex :: (Shape sh, Storable a) => Histogram sh a -> Int -> a Source #
Returns the value at the index as if the histogram was a single dimension vector (row-major representation).
assocs :: (Shape sh, Storable a) => Histogram sh a -> [(sh, a)] Source #
Returns all index/value pairs from the histogram.
pixToBin :: (HistogramShape (PixelValueSpace p), ToHistogram p) => PixelValueSpace p -> p -> PixelValueSpace p Source #
Given the number of bins of an histogram and a given pixel, returns the corresponding bin.
Histogram computations
histogram :: (MaskedImage i, ToHistogram (ImagePixel i), Storable a, Num a, HistogramShape (PixelValueSpace (ImagePixel i))) => Maybe (PixelValueSpace (ImagePixel i)) -> i -> Histogram (PixelValueSpace (ImagePixel i)) a Source #
Computes an histogram from a (possibly) multi-channel image.
If the size of the histogram is not given, there will be as many bins as the
range of values of pixels of the original image (see domainSize
).
If the size of the histogram is specified, every bin of a given dimension will be of the same size (uniform histogram).
histogram2D :: (Image i, ToHistogram (ImagePixel i), Storable a, Num a, HistogramShape (PixelValueSpace (ImagePixel i))) => ((PixelValueSpace (ImagePixel i) :. Int) :. Int) -> i -> Histogram ((PixelValueSpace (ImagePixel i) :. Int) :. Int) a Source #
Similar to histogram
but adds two dimensions for the y and x-coordinates
of the sampled points. This way, the histogram will map different regions of
the original image.
For example, an RGB
image will be mapped as
.Z
:.
red channel :.
green channel :.
blue channel :.
y region
:.
x region
As there is no reason to create an histogram as large as the number of pixels of the image, a size is always needed.
reduce :: (HistogramShape sh, Storable a, Num a) => Histogram ((sh :. Int) :. Int) a -> Histogram sh a Source #
Reduces a 2D histogram to its linear representation. See resize
for a
reduction of the number of bins of an histogram.
histogram
==reduce
.histogram2D
resize :: (HistogramShape sh, Storable a, Num a) => sh -> Histogram sh a -> Histogram sh a Source #
Resizes an histogram to another index shape. See reduce
for a reduction
of the number of dimensions of an histogram.
cumulative :: (Storable a, Num a) => Histogram DIM1 a -> Histogram DIM1 a Source #
Computes the cumulative histogram of another single dimension histogram.
C(i) = SUM H(j)
for each j
in [0..i]
where C
is the cumulative
histogram, and H
the original histogram.
normalize :: (Storable a, Real a, Storable b, Fractional b) => b -> Histogram sh a -> Histogram sh b Source #
Normalizes the histogram so that the sum of the histogram bins is equal to
the given value (normalisation by the L1
norm).
This is useful to compare two histograms which have been computed from images with a different number of pixels.
Images processing
equalizeImage :: (FunctorImage i i, Integral (ImagePixel i), ToHistogram (ImagePixel i), PixelValueSpace (ImagePixel i) ~ DIM1) => i -> i Source #
Equalizes a single channel image by equalising its histogram.
The algorithm equalizes the brightness and increases the contrast of the
image by mapping each pixel values to the value at the index of the
cumulative L1
-normalized histogram :
N(x, y) = H(I(x, y))
where N
is the equalized image, I
is the image and
H
the cumulative of the histogram normalized over an L1
norm.
Histogram comparisons
compareCorrel :: (Shape sh, Storable a, Real a, Storable b, Eq b, Floating b) => Histogram sh a -> Histogram sh a -> b Source #
Computes the Pearson's correlation coefficient between each corresponding bins of the two histograms.
A value of 1 implies a perfect correlation, a value of -1 a perfect opposition and a value of 0 no correlation at all.
compareCorrel
= SUM [ (H1(i) - µ(H1)) (H1(2) - µ(H2)) ]
/ ( SQRT [ SUM [ (H1(i) - µ(H1))^2 ] ]
* SQRT [ SUM [ (H2(i) - µ(H2))^2 ] ] )
Where µ(H)
is the average value of the histogram H
.
See http://en.wikipedia.org/wiki/Pearson_correlation_coefficient.
compareChi :: (Shape sh, Storable a, Real a, Storable b, Fractional b) => Histogram sh a -> Histogram sh a -> b Source #
Computes the Chi-squared distance between two histograms.
A value of 0 indicates a perfect match.
for each indice compareChi
= SUM (d(i))i
of the histograms where
d(i) = 2 * ((H1(i) - H2(i))^2 / (H1(i) + H2(i)))
.
compareIntersect :: (Shape sh, Storable a, Num a, Ord a) => Histogram sh a -> Histogram sh a -> a Source #
Computes the intersection of the two histograms.
The higher the score is, the best the match is.
for each indice compareIntersect
= SUM (min(H1(i), H2(i))i
of the
histograms.