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

Safe HaskellSafe-Inferred

Data.Image.Internal

Contents

Synopsis

Images

class Image i whereSource

An Image can be thought of as a 2 dimensional array of pixel values

Associated Types

type Pixel i :: *Source

The type of Pixel to be stored in images of type i.

Methods

makeImage :: Int -> Int -> PixelOp (Pixel i) -> iSource

Given an Int m, Int n, and a PixelOp f, returns an Image with dimensions m x n and the Pixel value at each (i, j) is (f i j)

>>> let gradient = makeImage 128 128 (\r c -> fromIntegral (r*c)) :: GrayImage
>>> gradient
< Image 128x128 >

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

ref :: i -> Int -> Int -> Pixel iSource

Given an Image i, row i, and column j, returns the Pixel in i at row i and column j.

>>> ref gradient 12 52
624.0

rows :: i -> IntSource

Given an Image i, returns the number of rows in i

>>> rows gradient
128

cols :: i -> IntSource

Given an Image i, returns the number of columns in i

>>> cols gradient
128

pixelList :: i -> [Pixel i]Source

Given an Image i, returns a list containing all of the pixels in i. The order in which the pixels are returned is from top left to bottom right.

>>> take 5 . reverse . pixelList $ gradient
[16129.0,16002.0,15875.0,15748.0,15621.0]

imageOp :: (Pixel i -> Pixel i -> Pixel i) -> i -> i -> iSource

Given a function of two pixel values to a pixel value f, an image X, and an image Y, return an Image that for each pixel value at (i,j) is the result of applying f to X(i,j) and Y(i,j). Note: The dimensions of X and Y must be equal otherwise the result of imageOp is undefined.

>>> let white = makeImage 128 128 (\ r c -> 8000) :: GrayImage
>>> let diff = imageOp (-) gradient white
>>> diff
< Image 128x128 >
>>> ref diff 0 0
-8000.0

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

Instances

type PixelOp px = Int -> Int -> pxSource

A function of a row and column that returns a pixel at that location

class MaxMin m whereSource

Methods

maximal :: [m] -> mSource

Given a [m] returns the maximal m in the list

minimal :: [m] -> mSource

Given a [m] returns the minimal m in the list

Instances

class Listable a whereSource

Something is Listable if it can be converted to a list. This type class is mostly for convenience when using leftToRight' and topToBottom'.

Associated Types

type Elem a :: *Source

The type of the elements in the list

Methods

toList :: a -> [Elem a]Source

Instances

Listable [a] 
Listable (a, a) 
Listable (a, a, a) 

Basic

dimensions :: Image i => i -> (Int, Int)Source

Given an Image i, return a pair (rows i, cols i)

>>> dimensions gradient
(128, 128)

maxIntensity :: (Image img, MaxMin (Pixel img)) => img -> Pixel imgSource

Given an Image i, returns the value of the Pixel with the maximal intensity

>>> maxIntensity gradient
16129.0
>>> maxIntensity cactii
RGB (254.0, 254.0, 254.0)

minIntensity :: (Image img, MaxMin (Pixel img)) => img -> Pixel imgSource

Given an Image i, returns the value of the Pixel with the minimal intensity

>>> minIntensity gradient
0.0
>>> minIntensity cactii
RGB (18.0, 18.0, 18.0)

transpose :: Image img => img -> imgSource

Given an Image i, returns an Image created by interchanging the rows and columns of i, i.e., the pixel value at location (i, j) of the resulting Image is the value of i at location (j, i).

>>> transpose frog
< Image 242x225 >

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

matrixProduct :: (Image img, Num (Pixel img)) => img -> img -> imgSource

Given an image X1 and an image X2, where the number of columns of X1 equals the number of rows of X2, matrixProduct returns an image representing the matrix product of X1 and X2.

>>> let cropped = crop 64 64 128 128 frog
>>> matrixProduct cropped cropped
< Image 128x128 >

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

medianFilter :: (Image img, Ord (Pixel img)) => Int -> Int -> img -> imgSource

Given two positive integers, m and n and a an image, medianFilter returns an image with the same dimensions where each pixel (i, j) in image is replaced by the pixel with median value in the neighborhood of size m times n centered on (i, j).

>>> medianFilter 5 5 frog
< Image 225x242 >

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

normalize :: (Image img, MaxMin (Pixel img), Fractional (Pixel img)) => img -> imgSource

Given img, normalize returns an image with the same dimensions where the values have been normalized to lie in the interval [0, 1].

>>> let normalfrog = normalize frog
>>> ref frog 0 0
151.0
>>> ref normalfrog 0 0
0.592156862745098

imageFold :: Image img => (Pixel img -> b -> b) -> b -> img -> bSource

Folds over the pixels of the provided image

>>> imageFold (+) 0 frog
6948219.0

imageMap :: (Image img, Image img') => (Pixel img -> Pixel img') -> img -> img'Source

Maps a function over each pixel in the provided image. When using Boxed images, you should use fmap instead.

>>> imageMap ((-1) *) frog :: GrayImage
< Image 225x242 >

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

(~>) :: (Image img, Ord (Pixel img)) => img -> Pixel img -> BoolSource

Given an image and a pixel value, returns True if and only if all values in the image are greater than the pixel value.

(~<) :: (Image img, Ord (Pixel img)) => img -> Pixel img -> BoolSource

Given an image and a pixel value, returns True if and only if all values in the image are less than the pixel value.

(<~) :: (Image img, Ord (Pixel img)) => Pixel img -> img -> BoolSource

Given a pixel value and an image, returns True if and only if all values in the image are greater than the pixel value.

(>~) :: (Image img, Ord (Pixel img)) => Pixel img -> img -> BoolSource

Given a pixel value and an image, returns True if and only if all values in the image are less than the pixel value.

Resizing Images

pad :: (Image img, Monoid (Pixel img)) => Int -> Int -> img -> imgSource

Given m, n, and img, pad returns an Image with m rows and n columns where the value at location (i, j) of the result image is the value of img at location (i, j) if i is less than m and j is less than n and mempty otherwise.

>>> pad 256 256 frog
< Image 256x256 >

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

crop :: Image img => Int -> Int -> Int -> Int -> img -> imgSource

Given a i0, j0, m, n, and img, crop returns an image with m rows and n columns where the value at location (i, j) of the result image is the value of img at location (i0 + i, j0 + j).

>>> crop 64 64 128 128 frog
< Image 128x128 >

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

downsampleRows :: Image img => img -> imgSource

Given img, downsampleRows returns the image created by discarding the odd numbered columns, i.e., the value at location (i, j) is the value of img at location (i, 2j).

>>> downsampleRows frog
< Image 225x121 >

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

downsampleCols :: Image img => img -> imgSource

Given img, downsampleCols returns the image created by discarding the odd numbered rows, i.e., the value at location (i, j) of the result image is the value of img at location (2i, j).

>>> downsampleCols frog
< Image 112x242 >

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

downsample :: Image img => img -> imgSource

Given img, downsample returns the image created by discarding the odd numbered rows and columns, i.e., the value at location (i, j) is the value of img at location (2i, 2j)

>>> let smallfrog = downsample frog
>>> smallfrog
< Image 112x121 >

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

upsampleRows :: (Image img, Monoid (Pixel img)) => img -> imgSource

Given img, upsampleRows returns an image with twice the number of columns where the value at location (i, j) of the result image is the value of img at location (i, j/2) if j is even and mempty otherwise.

>>> upsampleRows smallfrog
< Image 112x242 >

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

upsampleCols :: (Image img, Monoid (Pixel img)) => img -> imgSource

Given img, upsampleCols returns an image with twice the number of rows where the value at location (i, j) of the result image is the value of img at location (i/2, j) if i is even and mempty otherwise.

>>> upsampleCols smallfrog
< Image 224x121 >

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

upsample :: (Image img, Monoid (Pixel img)) => img -> imgSource

Given img, upsample returns an image with twice the number of rows and columns where the value at location (i, j) of the resulting image is the value of img at location (i2, j2) if i and jare are even and mempty otherwise.

>>> upsample smallfrog
< Image 224x242 >

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

Concatenation of Images

leftToRight :: Image img => img -> img -> imgSource

Given two images with the same number of rows X and Y, returns an image that is the concatenation of the two images from left to right.

>>> leftToRight frog frog
< Image 225x484 >

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

leftToRight' :: (Listable a, Image img, Image (Elem a), Elem a ~ img) => a -> imgSource

Given a Listable of images each of which have the same number of rows, returns an image that is the concatenation of all of the images from left to Right.

>>> leftToRight' . replicate 3 $ frog
< Image 225x726 >

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

topToBottom :: Image img => img -> img -> imgSource

Given two images with the same number of columns X and Y, returns an image that is the concatenation of the two images from top to bottom.

>>> topToBottom frog frog
< Image 450x242 >

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

topToBottom' :: (Listable a, Image img, Image (Elem a), Elem a ~ img) => a -> imgSource

Given a Listable of images all of which have the same number of columns, returns an image that is the concatenation of all of theimages from top to bottom.

>>> topToBottom' . replicate 3 $ frog
< Image 675x242 >

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

Images as Arrays

imageToArray :: Image img => img -> Array (Int, Int) (Pixel img)Source

Given img, returns an two dimensional array of Pixel values indexed by pairs of Ints where the fst is the row and snd is the column.

>>> let frogArr = imageToArray frog
>>> frogArr ! (0, 0)
151.0

arrayToImage :: Image img => Array (Int, Int) (Pixel img) -> imgSource

Given a two dimensional array of Pixel values indexed by pairs of Ints where the fst is the row and snd is the column, returns an Image.

>>> let img = arrayToImage (listArray ((0,0) (127,127)) [0..]) :: GrayImage
>>> img
< Image 128x128 >
>>> ref img 0 0
0.0
>>> ref img 0 10
10.0
>>> ref img 10 0
1280.0
>>> ref img 10 10
1290.0