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

Safe HaskellNone

Data.Image.Complex

Contents

Synopsis

Complex Images

class RealFloat (Value px) => ComplexPixel px whereSource

Associated Types

type Value px :: *Source

Methods

toComplex :: px -> Complex (Value px)Source

fromComplex :: Complex (Value px) -> pxSource

Discrete Fourier Transformations

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), Image img', Pixel img' ~ Complex (Value (Pixel img))) => img -> img'Source

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

>>> magnitude . imageMap log . fft $ frogpart

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), Image img', Pixel img' ~ Complex (Value (Pixel img))) => img -> img'Source

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

Converting Complex Images

complex :: (Image img, Image img', Pixel img' ~ Complex (Pixel img)) => img -> img -> img'Source

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

realPart :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> img'Source

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 . ifft $ (fft frogpart) * (fft d2g)

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

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

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

imagPart :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> img'Source

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 :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> img'Source

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

>>> magnitude signal

angle :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> img'Source

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

shrink :: (Image img, ComplexPixel (Pixel img)) => Value (Pixel img) -> img -> imgSource

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.

complexImageToRectangular :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> (img', img')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 :: (Image img, ComplexPixel (Pixel img), Image img', Pixel img' ~ Value (Pixel img)) => img -> (img', img')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