unm-hip-0.0.0.2: A Library for the manipulation of images

Safe HaskellNone

Data.Image.Boxed

Contents

Synopsis

Documentation

data BoxedImage a Source

BoxedImage is a concrete implementation of Image using a boxed internal structure. This allows for it to be installed nicely in Functor and Applicative.

Gray Images

type GrayImage = BoxedImage GraySource

A concrete instance of Image representing a gray scale image. This instance is installed in DisplayFormat as a gray PGM.

readImage :: FilePath -> IO GrayImageSource

Reads in a ASCII PGM image located at fileName as a GrayImage

>>> frog <- readImage "images/frog.pgm"

https://raw.github.com/jcollard/unm-hip/master/examples/frog.jpg

grayToComplex :: GrayImage -> ComplexImageSource

Coerces a GrayImage to a ComplexImage where the imaginary part for all pixels is 0.

>>> grayToComplex frog

makeHotImage :: GrayImage -> ColorImageSource

Given a GrayImage, makeHotImage returns a ColorImage with the same dimensions. The R, G, B values of the result image at (i, j) are determined by using the value of the ColorImage at (i, j) to index three lookup tables. These lookup tables implement a false coloring scheme which maps small values to black, large values to white, and intermediate values to shades of red, orange, and yellow (in that order).

>>> makeHotImage frog

https://raw.github.com/jcollard/unm-hip/master/examples/makehotimage.jpg

ref' :: GrayImage -> Double -> Double -> DoubleSource

Performs bilinear interpolation of a GrayImage at the coordinates provided.

Color Images

type ColorImage = BoxedImage ColorSource

A concrete instance of Image that represents images with color values. This instance is installed in DisplayFormat and can be written to a color PPM

data Color Source

A color encoding scheme

Constructors

RGB (Double, Double, Double)

Red, Green, Blue encoding

HSI (Double, Double, Double)

Hue, Saturation, Intensity encoding

readColorImage :: FilePath -> IO ColorImageSource

Reads in an ASCI PPM file as a ColorImage

>>> cactii <- readColorImage "images/cactii.ppm"

https://raw.github.com/jcollard/unm-hip/master/examples/cactii.jpg

colorImageRed :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Red color component

>>> let red = colorImageRed cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimagered.jpg

colorImageGreen :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Green color component

>>> let green = colorImageGreen cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimagegreen.jpg

colorImageBlue :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Blue color component

>>> let blue = colorImageBlue cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimageblue.jpg

colorImageToRGB :: ColorImage -> (GrayImage, GrayImage, GrayImage)Source

Given a ColorImage, returns a triple containing three GrayImages each containing one of the color components (red, green, blue)

>>> leftToRight' . colorImageToRGB $ cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimagetorgb.jpg

rgbToColorImage :: (GrayImage, GrayImage, GrayImage) -> ColorImageSource

Given a triple containing three GrayImages each containing one of the color components (red, green, blue), returns a ColorImage

>>> rgbToColorImage (red,green,blue)

https://raw.github.com/jcollard/unm-hip/master/examples/cactii.jpg

colorImageHue :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Hue component

>>> let h = colorImageHue cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimagehue.jpg

colorImageSaturation :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Saturation component

>>> let s = colorImageSaturation cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimagesaturation.jpg

colorImageIntensity :: ColorImage -> GrayImageSource

Given a ColorImage, returns a GrayImage representing the Intensity component

>>> let i = colorImageIntensity cactii

https://raw.github.com/jcollard/unm-hip/master/examples/colorimageintensity.jpg

colorImageToHSI :: ColorImage -> (GrayImage, GrayImage, GrayImage)Source

Given a ColorImage, returns a triple containing three GrayImages each containing one of the components (hue, saturation, intensity)

>>> let (h, s, i) = colorImageToHSI $ cactii

hsiToColorImage :: (GrayImage, GrayImage, GrayImage) -> ColorImageSource

Given a triple containing three GrayImages each containing one of the color components (hue, saturation, ), returns a ColorImage

>>> hsiToColorImage (h, s, i)

https://raw.github.com/jcollard/unm-hip/master/examples/cactii.jpg

Complex Images

type ComplexImage = BoxedImage ComplexSource

A concrete instance of Image representing pixels as complex values. This instance can be written to file as a color PPM.

makeFilter :: Image img => Int -> Int -> PixelOp (Pixel img) -> imgSource

Given a positive integer m, a positive integer n, and a function returning a pixel value, makeFilter returns an image with m rows and n columns. Let x equal i if i is less than m/2 and i - m otherwise and let y equal j if j is less than n/2 and j - n otherwise. To match the periodicity of the 2D discrete Fourier spectrum, the value of the result image at location (i, j) is computed by applying the function to x and y, e.g., the value at location (0, 0) is the result of applying the function to 0 and 0, the value at (m-1, n-1) is the result of applying function to -1 and -1.

>>> makeFilter 128 128 (\ r c -> fromIntegral (r + c)) :: GrayImage
< Image 128x128 >

https://raw.github.com/jcollard/unm-hip/master/examples/makefilter.jpg

    laplacianOfGaussian :: Double -> Int -> Int -> Double
    laplacianOfGaussian stddev i j = ((-pi) / (stddev*stddev)) * (1 - x) * (exp (-x)) where
      r = fromIntegral $ i*i + j*j
      x = r / (2.0*stddev)
>>> let d2g = makeFilter 128 128 (laplacianOfGaussian 8) :: GrayImage

https://raw.github.com/jcollard/unm-hip/master/examples/d2g.jpg

    gaussian :: Double -> Int -> Int -> Double 
    gaussian variance i j = exp (-x) where
      r = fromIntegral $ i*i + j*j
      x = r / (2.0*pi*variance)
>>> let g = makeFilter 128 128 (gaussian 8) :: GrayImage

https://raw.github.com/jcollard/unm-hip/master/examples/g.jpg

fft :: (Image img, ComplexPixel (Pixel img), Value (Pixel img) ~ Double) => img -> ComplexImageSource

Given an image whose pixels can be converted to a complex value, fft returns an image with complex pixels representing its 2D discrete Fourier transform (DFT). Because the DFT is computed using the Fast Fourier Transform (FFT) algorithm, the number of rows and columns of the image must both be powers of two, i.e., 2K where K is an integer.

>>> frog <- readImage "images/frog.pgm"
>>> let frogpart = crop 64 64 128 128 frog

https://raw.github.com/jcollard/unm-hip/master/examples/frog.jpg

https://raw.github.com/jcollard/unm-hip/master/examples/frogpart.jpg

>>> imageMap log . fft $ frogpart :: ComplexImage

https://raw.github.com/jcollard/unm-hip/master/examples/fft.jpg

>>> fft d2g

https://raw.github.com/jcollard/unm-hip/master/examples/fftd2g.jpg

>>> fft g

https://raw.github.com/jcollard/unm-hip/master/examples/fftg.jpg

ifft :: (Image img, ComplexPixel (Pixel img), Value (Pixel img) ~ Double) => img -> ComplexImageSource

Given an image, ifft returns a complex image representing its 2D inverse discrete Fourier transform (DFT). Because the inverse DFT is computed using the Fast Fourier Transform (FFT) algorithm, the number of rows and columns of image must both be powers of two, i.e., 2K where K is an integer.

>>> ifft ((fft frogpart) * (fft d2g))

https://raw.github.com/jcollard/unm-hip/master/examples/ifft.jpg

>>> ifft ((fft frogpart) * (fft g))

https://raw.github.com/jcollard/unm-hip/master/examples/ifft2.jpg

realPart :: ComplexImage -> GrayImageSource

Given a complex image, returns a real image representing the real part of the image.

    harmonicSignal :: Double -> Double -> Int -> Int -> C.Complex Double
    harmonicSignal u v m n = exp (-pii*2.0 * var) where 
      pii = 0.0 C.:+ pi
      var = (u*m' + v*n') C.:+ 0.0
      [m',n'] = map fromIntegral [m, n]
>>> let signal = makeImage 128 128 (harmonicSignal (3/128) (2/128)) :: ComplexImage

https://raw.github.com/jcollard/unm-hip/master/examples/signal.jpg

>>> let cosine = realPart signal

https://raw.github.com/jcollard/unm-hip/master/examples/cosine.jpg

>>> realPart realPart . ifft $ (fft frogpart) * (fft d2g)

https://raw.github.com/jcollard/unm-hip/master/examples/realpart.jpg

>>> realPart realPart . ifft $ (fft frogpart) * (fft g)

https://raw.github.com/jcollard/unm-hip/master/examples/realpart2.jpg

imagPart :: ComplexImage -> GrayImageSource

Given a complex image, returns a real image representing the imaginary part of the image

>>> let sine = imagPart signal

https://raw.github.com/jcollard/unm-hip/master/examples/sine.jpg

magnitude :: ComplexImage -> GrayImageSource

Given a complex image, returns a real image representing the magnitude of the image.

>>> magnitude signal

angle :: ComplexImage -> GrayImageSource

Given a complex image, returns a real image representing the angle of the image

>>> angle signal

https://raw.github.com/jcollard/unm-hip/master/examples/angle.jpg

complex :: GrayImage -> GrayImage -> ComplexImageSource

Given an image representing the real part of a complex image, and an image representing the imaginary part of a complex image, returns a complex image.

>>> complex cosine sine

https://raw.github.com/jcollard/unm-hip/master/examples/signal.jpg

complexImageToRectangular :: ComplexImage -> (GrayImage, GrayImage)Source

Given a complex image, return a pair of real images each representing a component of the complex image (real, imaginary).

>>> leftToRight' . complexImageToRectangular $ signal

https://raw.github.com/jcollard/unm-hip/master/examples/complexsignaltorectangular.jpg

complexImageToPolar :: ComplexImage -> (GrayImage, GrayImage)Source

Given a complex image, returns a pair of real images each representing the component (magnitude, phase) of the image

>>> leftToRight' . complexImageToPolar $ signal

https://raw.github.com/jcollard/unm-hip/master/examples/compleximagetopolar.jpg

shrink :: (Num a, Image img, ComplexPixel (Pixel img), Value (Pixel img) ~ Double) => a -> img -> ComplexImageSource

Given a complex image and a real positive number x, shrink returns a complex image with the same dimensions. Let z be the value of the image at location (i, j). The value of the complex result image at location (i, j) is zero if |z| < x, otherwise the result has the same phase as z but the amplitude is decreased by x.

Binary Images

distanceTransform :: (Image img, BinaryPixel (Pixel img)) => img -> GrayImageSource

Given a binary image, distanceTransform returns an image representing the 2D distance transform of the image. The distance transform is accurate to within a 2% error for euclidean distance.

>>> distanceTransform binaryStop :: GrayImage
< Image 86x159 >

https://raw.github.com/jcollard/unm-hip/master/examples/distancetransform.jpg

label :: (Image img, BinaryPixel (Pixel img)) => img -> GrayImageSource

Given a binary image, label returns an image where pixels in distinct connected components (based on 4-neighbor connectivity) have distinct integer values. These values range from 1 to n where n is the number of connected components in image.

>>> label binaryStop
< Image 86x159 >

https://raw.github.com/jcollard/unm-hip/master/examples/label.jpg

Additional Modules

Contains functionality for performing arithmetic operations on images with scalar values.

Contains functionality related to Binary Images

Contains functionality for convolution of images

Contains basic functionality for Images

Contains functionality for writing images and displaying with an external program