Copyright | (c) Alexey Kuleshevich 2016 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- toImageBinaryUsing :: (Array arr cs e, Array arr Binary Bit) => (Pixel cs e -> Bool) -> Image arr cs e -> Image arr Binary Bit
- toImageBinaryUsing2 :: (Array arr cs e, Array arr Binary Bit) => (Pixel cs e -> Pixel cs e -> Bool) -> Image arr cs e -> Image arr cs e -> Image arr Binary Bit
- thresholdWith :: (Array arr cs e, Array arr Binary Bit) => Pixel cs (e -> Bool) -> Image arr cs e -> Image arr Binary Bit
- compareWith :: (Array arr cs e1, Array arr cs e2, Array arr Binary Bit) => Pixel cs (e1 -> e2 -> Bool) -> Image arr cs e1 -> Image arr cs e2 -> Image arr Binary Bit
- (.&&.) :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
- (.||.) :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
- invert :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit
- class Array arr Binary Bit => Thresholding a b arr | a b -> arr where
- (.==.) :: (Eq (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- (./=.) :: (Eq (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- (.<.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- (.<=.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- (.>.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- (.>=.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit
- erode :: ManifestArray arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
- dialate :: ManifestArray arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
- open :: ManifestArray arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
- close :: ManifestArray arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit
Construction
:: (Array arr cs e, Array arr Binary Bit) | |
=> (Pixel cs e -> Bool) | Predicate |
-> Image arr cs e | Source image. |
-> Image arr Binary Bit |
Construct a binary image using a predicate from a source image.
:: (Array arr cs e, Array arr Binary 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 Binary Bit |
Construct a binary image using a predicate from two source images.
:: (Array arr cs e, Array arr Binary Bit) | |
=> Pixel cs (e -> Bool) | Pixel containing a thresholding function per channel. |
-> Image arr cs e | Source image. |
-> Image arr Binary Bit |
Threshold a source image with an applicative pixel.
>>>
yield <- readImageRGB "images/yield.jpg"
>>>
writeImageExact PNG [] "images/yield_bin.png" $ thresholdWith (PixelRGB (>0.55) (<0.6) (<0.5)) yield
:: (Array arr cs e1, Array arr cs e2, Array arr Binary 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 Binary Bit |
Compare two images with an applicative pixel. Works just like
thresholdWith
, but on two images.
Bitwise operations
(.&&.) :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit infixr 3 Source
Pixel wise AND
operator on binary images.
(.||.) :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit -> Image arr Binary Bit infixr 2 Source
Pixel wise OR
operator on binary images.
invert :: Array arr Binary Bit => Image arr Binary Bit -> Image arr Binary Bit Source
Complement each pixel in the image
Thresholding
class Array arr Binary Bit => 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.
(.==.) :: (Eq (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
(./=.) :: (Eq (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
(.<.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
(.>.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
(.>=.) :: (Ord (Pixel cs e), Array arr cs e) => a cs e -> b cs e -> Image arr Binary Bit infix 4 Source
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.
figure :: Image VU Binary 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 Binary Bit struct = fromLists [[0,1],[1,1],[0,1]]
:: ManifestArray arr Binary Bit | |
=> Image arr Binary Bit | Structuring element. |
-> Image arr Binary Bit | Binary source image. |
-> Image arr Binary 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
:: ManifestArray arr Binary Bit | |
=> Image arr Binary Bit | Structuring element. |
-> Image arr Binary Bit | Binary source image. |
-> Image arr Binary 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
:: ManifestArray arr Binary Bit | |
=> Image arr Binary Bit | Structuring element. |
-> Image arr Binary Bit | Binary source image. |
-> Image arr Binary Bit |
Opening is defined as: {B ○ S = (B ⊖ S) ⊕ S}
>>>
writeImageExact PNG [] "images/figure_open.png" $ pixelGrid 10 $ fromImageBinary $ open struct figure
opened with is
:: ManifestArray arr Binary Bit | |
=> Image arr Binary Bit | Structuring element. |
-> Image arr Binary Bit | Binary source image. |
-> Image arr Binary Bit |
Closing is defined as: {B ● S = (B ⊕ S) ⊖ S}
>>>
writeImageExact PNG [] "images/figure_close.png" $ pixelGrid 10 $ fromImageBinary $ close struct figure
closed with is