Copyright | (c) Alexey Kuleshevich 2017 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- toImageBinaryUsing :: (Array arr cs e, Array arr X Bit) => (Pixel cs e -> Bool) -> Image arr cs e -> Image arr X Bit
- toImageBinaryUsing2 :: (Array arr cs e, Array arr X Bit) => (Pixel cs e -> Pixel cs e -> Bool) -> Image arr cs e -> Image arr cs e -> Image arr X Bit
- threshold :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs (e -> Bool) -> Image arr cs e -> Image arr cs Bit
- threshold2 :: (Applicative (Pixel cs), Array arr cs e', Array arr cs e, Array arr cs Bit) => Pixel cs (e' -> e -> Bool) -> Image arr cs e' -> Image arr cs e -> Image arr cs Bit
- thresholdWith :: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e, Array arr X Bit) => Pixel cs (e -> Bool) -> Image arr cs e -> Image arr X Bit
- thresholdWith2 :: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e1, Array arr cs e2, Array arr X Bit) => Pixel cs (e1 -> e2 -> Bool) -> Image arr cs e1 -> Image arr cs e2 -> Image arr X Bit
- compareWith :: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e1, Array arr cs e2, Array arr X Bit) => Pixel cs (e1 -> e2 -> Bool) -> Image arr cs e1 -> Image arr cs e2 -> Image arr X Bit
- class Thresholding a b arr | a b -> arr where
- (!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (!<!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (!<=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (!>!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (!>=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit
- (.==.) :: (Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- (./=.) :: (Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- (.<.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- (.<=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- (.>.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- (.>=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit
- or :: Array arr X Bit => Image arr X Bit -> Bool
- and :: Array arr X Bit => Image arr X Bit -> Bool
- (!&&!) :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit -> Image arr cs Bit
- (!||!) :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit -> Image arr cs Bit
- (.&&.) :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr cs Bit -> Image arr X Bit
- (.||.) :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr cs Bit -> Image arr X Bit
- invert :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit
- disjunction :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr X Bit
- conjunction :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr X Bit
- erode :: Array arr X Bit => Image arr X Bit -> Image arr X Bit -> Image arr X Bit
- dialate :: Array arr X Bit => Image arr X Bit -> Image arr X Bit -> Image arr X Bit
- open :: Array arr X Bit => Image arr X Bit -> Image arr X Bit -> Image arr X Bit
- close :: Array arr X Bit => Image arr X Bit -> Image arr X Bit -> Image arr X Bit
Construction
:: (Array arr cs e, Array arr X Bit) | |
=> (Pixel cs e -> Bool) | Predicate |
-> Image arr cs e | Source image. |
-> Image arr X Bit |
Construct a binary image using a predicate from a source image.
:: (Array arr cs e, Array arr X Bit) | |
=> (Pixel cs e -> Pixel cs e -> Bool) | Predicate |
-> Image arr cs e | First source image. |
-> Image arr cs e | Second source image. |
-> Image arr X Bit |
Construct a binary image using a predicate from two source images.
threshold :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs (e -> Bool) -> Image arr cs e -> Image arr cs Bit Source #
threshold2 :: (Applicative (Pixel cs), Array arr cs e', Array arr cs e, Array arr cs Bit) => Pixel cs (e' -> e -> Bool) -> Image arr cs e' -> Image arr cs e -> Image arr cs Bit Source #
:: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e, Array arr X Bit) | |
=> Pixel cs (e -> Bool) | Pixel containing a thresholding function per channel. |
-> Image arr cs e | Source image. |
-> Image arr X Bit |
Threshold a source image with an applicative pixel.
>>>
yield <- readImageRGB VU "images/yield.jpg"
>>>
writeImageExact PNG [] "images/yield_bin.png" $ thresholdWith (PixelRGB (>0.55) (<0.6) (<0.5)) yield
:: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e1, Array arr cs e2, Array arr X Bit) | |
=> Pixel cs (e1 -> e2 -> Bool) | Pixel containing a comparing function per channel. |
-> Image arr cs e1 | First image. |
-> Image arr cs e2 | second image. |
-> Image arr X Bit |
Compare two images with an applicative pixel. Works just like
thresholdWith
, but on two images.
:: (Applicative (Pixel cs), Foldable (Pixel cs), Array arr cs e1, Array arr cs e2, Array arr X Bit) | |
=> Pixel cs (e1 -> e2 -> Bool) | Pixel containing a comparing function per channel. |
-> Image arr cs e1 | First image. |
-> Image arr cs e2 | second image. |
-> Image arr X Bit |
Deprecated: Use thresholdWith2
instead.
Compare two images with an applicative pixel. Works just like
thresholdWith
, but on two images.
Thresholding
class Thresholding a b arr | a b -> arr where Source #
Thresholding
contains a convenient set of functions for binary image
construction, which is done by comparing either a single pixel with every
pixel in an image or two same size images pointwise. For example:
>>>
frog <- readImageY VU "images/frog.jpg"
>>>
frog .==. PixelY 0 -- (or: PixelY 0 .==. frog)
>>>
frog .<. flipH frog -- (or: flipH frog .>. frog)
(!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(!<!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(!<=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(!>!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(!>=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => a cs e -> b cs e -> Image arr cs Bit infix 4 Source #
(.==.) :: (Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
(./=.) :: (Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
(.<.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
(.<=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
(.>.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
(.>=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => a cs e -> b cs e -> Image arr X Bit infix 4 Source #
Instances
Array arr X Bit => Thresholding Pixel (Image arr) arr Source # | |
Defined in Graphics.Image.Processing.Binary (!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (!<!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (!<=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (!>!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (!>=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source # (.==.) :: (Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # (./=.) :: (Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # (.<.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # (.<=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # (.>.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # (.>=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Pixel cs e -> Image arr cs e -> Image arr X Bit Source # | |
Array arr X Bit => Thresholding (Image arr) Pixel arr Source # | |
Defined in Graphics.Image.Processing.Binary (!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (!<!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (!<=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (!>!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (!>=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source # (.==.) :: (Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # (./=.) :: (Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # (.<.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # (.<=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # (.>.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # (.>=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Pixel cs e -> Image arr X Bit Source # | |
Thresholding (Image arr) (Image arr) arr Source # | |
Defined in Graphics.Image.Processing.Binary (!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (!<!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (!<=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (!>!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (!>=!) :: (Ord e, Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Image arr cs e -> Image arr cs Bit Source # (.==.) :: (Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # (./=.) :: (Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # (.<.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # (.<=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # (.>.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # (.>=.) :: (Ord (Pixel cs e), Array arr cs e, Array arr X Bit) => Image arr cs e -> Image arr cs e -> Image arr X Bit Source # |
Bitwise operations
or :: Array arr X Bit => Image arr X Bit -> Bool Source #
Disjunction of all pixels in a Binary image
and :: Array arr X Bit => Image arr X Bit -> Bool Source #
Conjunction of all pixels in a Binary image
(!&&!) :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit -> Image arr cs Bit infixr 3 Source #
Pixel wise AND
operator on binary images.
(!||!) :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit -> Image arr cs Bit infixr 2 Source #
Pixel wise OR
operator on binary images.
(.&&.) :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr cs Bit -> Image arr X Bit infixr 3 Source #
Pixel wise AND
operator on binary images. Unlike !&&!
this operator
will also AND
pixel componenets.
(.||.) :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr cs Bit -> Image arr X Bit infixr 2 Source #
Pixel wise OR
operator on binary images. Unlike !||!
this operator
will also OR
pixel componenets.
invert :: Array arr cs Bit => Image arr cs Bit -> Image arr cs Bit Source #
Complement each pixel in a binary image
disjunction :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr X Bit Source #
Join each component of a pixel with a binary
operator..|.
conjunction :: (Array arr cs Bit, Array arr X Bit) => Image arr cs Bit -> Image arr X Bit Source #
Join each component of a pixel with a binary
operator..&.
Binary Morphology
In order to demonstrate how morphological operations work, a
binary source image = B constructed here together with a structuring element
= S will be used in examples that follow. Origin of the structuring
element is always at it's center, eg. (1,1)
for the one below.
figure :: Image VU X Bit figure = fromLists [[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,0,0,0], [0,0,0,0,0,0,1,0,0,0,0,0,0,0,0,0,0], [0,0,0,0,0,0,1,1,0,0,0,0,0,1,1,1,0], [0,0,0,0,0,0,0,1,0,0,0,0,1,1,0,0,0], [0,0,0,0,0,0,0,0,0,0,1,0,0,0,0,0,0], [0,0,0,0,0,0,0,0,0,0,1,0,0,0,0,0,0], [0,0,0,0,1,1,1,1,1,1,1,0,0,0,0,0,0], [0,0,0,0,1,1,1,1,1,1,1,0,0,0,0,0,0], [0,0,0,0,0,0,1,1,1,1,1,0,0,0,0,0,0], [0,0,0,0,0,0,1,1,1,1,0,0,0,1,0,0,0], [0,0,0,0,0,0,1,1,1,1,0,0,0,0,0,0,0], [0,0,0,0,1,0,0,0,0,0,0,0,0,0,0,0,0], [0,0,0,0,1,0,0,0,0,0,0,0,0,0,0,0,0], [0,0,0,0,0,0,0,0,0,1,1,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,0,0,0,0,0,0,0,0,0]] struct :: Image VU X Bit struct = fromLists [[0,1,0],[1,1,0],[0,1,0]]
:: Array arr X Bit | |
=> Image arr X Bit | Structuring element. |
-> Image arr X Bit | Binary source image. |
-> Image arr X Bit |
Erosion is defined as: {E = B ⊖ S = {m,n|Sₘₙ⊆B}
>>>
writeImageExact PNG [] "images/figure_erode.png" $ pixelGrid 10 $ fromImageBinary $ erode struct figure
eroded with is
:: Array arr X Bit | |
=> Image arr X Bit | Structuring element. |
-> Image arr X Bit | Binary source image. |
-> Image arr X Bit |
Dialation is defined as: {D = B ⊕ S = {m,n|Sₘₙ∩B≠∅}
>>>
writeImageExact PNG [] "images/figure_dialate.png" $ pixelGrid 10 $ fromImageBinary $ dialate struct figure
dialated with is