hip-1.5.5.0: Haskell Image Processing (HIP) Library.

Copyright(c) Alexey Kuleshevich 2017
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Graphics.Image

Contents

Description

Haskell Image Processing (HIP) library is a wrapper around any array like data structure and is fully agnostic to the underlying representation. All of the functionality in this library relies upon a few type classes, which corresponding representation types are instances of:

  • Array arr cs e - this is a base class for every Image arr cs e, where arr stands for an underlying array representation, cs is the ColorSpace of an image and e is the type denoting precision of an image (Int, Word, Double, etc.) .
  • MArray arr cs e - is a kind of array, that can be indexed in constant time and allows monadic operations and mutation on MImage st arr cs e, which is Image's mutable cousin.

Representations using Vector and Repa packages:

  • VU - Vector Unboxed representation.
  • VS - Vector Storable representation.
  • RSU - Repa Sequential Unboxed array representation (computation is done sequentially).
  • RPU - Repa Parallel Unboxed array representation (computation is done in parallel).
  • RSS - Repa Sequential Storable array representation (computation is done sequentially).
  • RPS - Repa Parallel Storable array representation (computation is done in parallel).

Images with RSU, RSS, RPU and RPS types, most of the time, hold functions rather than an actual data, this way computation can be fused together, and later changed to VU or VS using toManifest, which in turn performs the fused computation. If at any time computation needs to be forced, compute can be used for that purpose.

Many of the function names exported by this module will clash with the ones from Prelude, hence it can be more convenient to import like this:

import Prelude as P
import Graphics.Image as I
Synopsis

Color Space

Here is a list of default Pixels with their respective constructors:

    * Pixel Y e      = PixelY y              - Luma, also commonly denoted as Y'.
    * Pixel YA e     = PixelYA y a           - Luma with alpha.
    * Pixel RGB e    = PixelRGB r g b        - Red, Green and Blue.
    * Pixel RGBA e   = PixelRGBA r g b a     - RGB with alpha
    * Pixel HSI e    = PixelHSI h s i        - Hue, Saturation and Intensity.
    * Pixel HSIA e   = PixelHSIA h s i a     - HSI with alpha
    * Pixel CMYK e   = PixelCMYK c m y k     - Cyan, Magenta, Yellow and Key (Black).
    * Pixel CMYKA e  = PixelCMYKA c m y k a  - CMYK with alpha.
    * Pixel YCbCr e  = PixelYCbCr y cb cr    - Luma, blue-difference and red-difference chromas.
    * Pixel YCbCrA e = PixelYCbCrA y cb cr a - YCbCr with alpha.
      ------------------------------------------------------------------------------------------
    * Pixel X Bit          = on | off - Bi-tonal.
    * Pixel cs (Complex e) = (Pixel cs e) +: (Pixel cs e) - Complex pixels with any color space.
    * Pixel X e         = PixelX g - Used to represent binary images as well as any other single channel colorspace, for instance to separate channels from other color spaces into standalone images.

Every Pixel is an instance of Functor, Applicative, Foldable and Num, as well as Floating and Fractional if e is also an instance.

All of the functionality related to every ColorSpace is re-exported by Graphics.Image.Types module.

Creation

makeImageR Source #

Arguments

:: Array arr cs e 
=> arr

Underlying image representation.

-> (Int, Int)

(m rows, n columns) - dimensions of a new image.

-> ((Int, Int) -> Pixel cs e)

A function that takes (i-th row, and j-th column) as an argument and returns a pixel for that location.

-> Image arr cs e 

Create an image with a specified representation and pixels of Double precision. Note, that it is essential for Double precision pixels to keep values normalized in the [0, 1] range in order for an image to be written to file properly.

>>> let grad_gray = makeImageR VU (200, 200) (\(i, j) -> PixelY (fromIntegral i) / 200 * (fromIntegral j) / 200)

Because all Pixels and Images are installed into Num, above is equivalent to:

>>> let grad_gray = makeImageR RPU (200, 200) (\(i, j) -> PixelY $ fromIntegral (i*j)) / (200*200)
>>> writeImage "images/grad_gray.png" (grad_gray :: Image RPU Y Double)

Creating color images is just as easy.

>>> let grad_color = makeImageR VU (200, 200) (\(i, j) -> PixelRGB (fromIntegral i) (fromIntegral j) (fromIntegral (i + j))) / 400
>>> writeImage "images/grad_color.png" grad_color

makeImage Source #

Arguments

:: Array arr cs e 
=> (Int, Int)

(m rows, n columns) - dimensions of a new image.

-> ((Int, Int) -> Pixel cs e)

A function that takes (i-th row, and j-th column) as an argument and returns a pixel for that location.

-> Image arr cs e 

Create an Image by supplying it's dimensions and a pixel generating function.

fromListsR :: Array arr cs e => arr -> [[Pixel cs e]] -> Image arr cs e Source #

Type restricted version of fromLists that constructs an image using supplied representation.

fromLists :: Array arr cs e => [[Pixel cs e]] -> Image arr cs e Source #

Construct an image from a nested rectangular shaped list of pixels. Length of an outer list will constitute m rows, while the length of inner lists - n columns. All of the inner lists must be the same length and greater than 0.

>>> fromLists [[PixelY (fromIntegral (i*j) / 60000) | j <- [1..300]] | i <- [1..200]]
<Image VectorUnboxed Y (Double): 200x300>

toLists :: MArray arr cs e => Image arr cs e -> [[Pixel cs e]] Source #

Generates a nested list of pixels from an image.

 img == fromLists (toLists img)

IO

Reading

Read supported files into an Image with pixels in Double precision. In order to read an image in a different representation, color space or precision, use readImage or readImageExact from Graphics.Image.IO instead. While reading an image, it's underlying representation can be specified by passing one of VU, VS, RSU, RPU, RSS or RSU as the first argument to readImage* functions. Here is a quick demonstration of how two images can be read as different representations and later easily combined as their average.

>>> cluster <- readImageRGB VU "images/cluster.jpg"
>>> displayImage cluster
>>> centaurus <- readImageRGB VU "images/centaurus.jpg"
>>> displayImage centaurus
>>> displayImage ((cluster + centaurus) / 2)

readImageY :: Array arr Y Double => arr -> FilePath -> IO (Image arr Y Double) Source #

Read image as luma (brightness).

readImageYA :: Array arr YA Double => arr -> FilePath -> IO (Image arr YA Double) Source #

Read image as luma with Alpha channel.

readImageRGB :: Array arr RGB Double => arr -> FilePath -> IO (Image arr RGB Double) Source #

Read image in RGB colorspace.

readImageRGBA :: Array arr RGBA Double => arr -> FilePath -> IO (Image arr RGBA Double) Source #

Read image in RGB colorspace with Alpha channel.

Writing

writeImage Source #

Arguments

:: (Array VS cs e, Array arr cs e, Writable (Image VS cs e) OutputFormat) 
=> FilePath

Location where an image should be written.

-> Image arr cs e

An image to write.

-> IO () 

Just like readImage, this function will guess an output file format from the extension and write to file any image that is in one of Y, YA, RGB or RGBA color spaces with Double precision. While doing necessary conversions the choice will be given to the most suited color space supported by the format. For instance, in case of a PNG format, an (Image arr RGBA Double) would be written as RGBA16, hence preserving transparency and using highest supported precision Word16. At the same time, writing that image in GIF format would save it in RGB8, since Word8 is the highest precision GIF supports.

displayImage Source #

Arguments

:: (Array VS cs e, Array arr cs e, Writable (Image VS cs e) TIF) 
=> Image arr cs e

Image to be displayed

-> IO () 

Makes a call to an external viewer that is set as a default image viewer by the OS. This is a non-blocking function call, so it might take some time before an image will appear.

Accessors

Dimensions

rows :: BaseArray arr cs e => Image arr cs e -> Int Source #

Get the number of rows in an image.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> frog
<Image VectorUnboxed RGB (Double): 200x320>
>>> rows frog
200

cols :: BaseArray arr cs e => Image arr cs e -> Int Source #

Get the number of columns in an image.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> frog
<Image VectorUnboxed RGB (Double): 200x320>
>>> cols frog
320

dims :: BaseArray arr cs e => Image arr cs e -> (Int, Int) Source #

Get dimensions of an image.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> frog
<Image VectorUnboxed RGB (Double): 200x320>
>>> dims frog
(200,320)

Indexing

index :: MArray arr cs e => Image arr cs e -> (Int, Int) -> Pixel cs e Source #

Get a pixel at i-th and j-th location.

>>> let grad_gray = makeImage (200, 200) (\(i, j) -> PixelY $ fromIntegral (i*j)) / (200*200)
>>> index grad_gray (20, 30) == PixelY ((20*30) / (200*200))
True

maybeIndex :: MArray arr cs e => Image arr cs e -> (Int, Int) -> Maybe (Pixel cs e) Source #

Image indexing function that returns Nothing if index is out of bounds, Just px otherwise.

defaultIndex :: MArray arr cs e => Pixel cs e -> Image arr cs e -> (Int, Int) -> Pixel cs e Source #

Image indexing function that returns a default pixel if index is out of bounds.

borderIndex :: MArray arr cs e => Border (Pixel cs e) -> Image arr cs e -> (Int, Int) -> Pixel cs e Source #

Image indexing function that uses a special border resolutions strategy for out of bounds pixels.

Transformation

Pointwise

map Source #

Arguments

:: (Array arr cs e, Array arr cs' e') 
=> (Pixel cs' e' -> Pixel cs e)

A function that takes a pixel of a source image and returns a pixel for the result image a the same location.

-> Image arr cs' e'

Source image.

-> Image arr cs e

Result image.

Map a function over a an image.

imap Source #

Arguments

:: (Array arr cs e, Array arr cs' e') 
=> ((Int, Int) -> Pixel cs' e' -> Pixel cs e)

A function that takes an index (i, j), a pixel at that location and returns a new pixel at the same location for the result image.

-> Image arr cs' e'

Source image.

-> Image arr cs e

Result image.

Map an index aware function over each pixel in an image.

zipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => (Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e Source #

Zip two images with a function

izipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => ((Int, Int) -> Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e Source #

Zip two images with an index aware function

Geometric

traverse Source #

Arguments

:: (Array arr cs e, Array arr cs' e') 
=> Image arr cs' e'

Source image.

-> ((Int, Int) -> (Int, Int))

Function that takes dimensions of a source image and returns dimensions of a new image.

-> (((Int, Int) -> Pixel cs' e') -> (Int, Int) -> Pixel cs e)

Function that receives a pixel getter (a source image index function), a location (i, j) in a new image and returns a pixel for that location.

-> Image arr cs e 

Traverse an image

traverse2 Source #

Arguments

:: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) 
=> Image arr cs1 e1

First source image.

-> Image arr cs2 e2

Second source image.

-> ((Int, Int) -> (Int, Int) -> (Int, Int))

Function that produces dimensions for the new image.

-> (((Int, Int) -> Pixel cs1 e1) -> ((Int, Int) -> Pixel cs2 e2) -> (Int, Int) -> Pixel cs e)

Function that produces pixels for the new image.

-> Image arr cs e 

Traverse two images.

transpose :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Transpose an image

backpermute Source #

Arguments

:: Array arr cs e 
=> (Int, Int)

Dimensions of a result image.

-> ((Int, Int) -> (Int, Int))

Function that maps an index of a result image to an index of a source image.

-> Image arr cs e

Source image.

-> Image arr cs e

Result image.

Backwards permutation of an image.

(|*|) :: Array arr cs e => Image arr cs e -> Image arr cs e -> Image arr cs e Source #

Perform matrix multiplication on two images. Inner dimensions must agree.

Reduction

fold Source #

Arguments

:: Array arr cs e 
=> (Pixel cs e -> Pixel cs e -> Pixel cs e)

An associative folding function.

-> Pixel cs e

Initial element, that is neutral with respect to the folding function.

-> Image arr cs e

Source image.

-> Pixel cs e 

Undirected reduction of an image.

sum :: Array arr cs e => Image arr cs e -> Pixel cs e Source #

Sum all pixels in the image.

product :: Array arr cs e => Image arr cs e -> Pixel cs e Source #

Multiply all pixels in the image.

maximum :: (Array arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e Source #

Retrieve the biggest pixel from an image

minimum :: (Array arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e Source #

Retrieve the smallest pixel from an image

normalize :: (Array arr cs e, Array arr X e, Fractional e, Ord e) => Image arr cs e -> Image arr cs e Source #

Scales all of the pixels to be in the range [0, 1].

eqTol :: (Array arr X Bit, Array arr cs e, Ord e) => e -> Image arr cs e -> Image arr cs e -> Bool Source #

Check weather two images are equal within a tolerance. Useful for comparing images with Float or Double precision.

Manifest Image

Representations

exchange Source #

Arguments

:: (Array arr' cs e, Array arr cs e) 
=> arr

New representation of an image.

-> Image arr' cs e

Source image.

-> Image arr cs e 

Exchange the underlying array representation of an image.

Sampling

downsampleRows :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Downsample an image by discarding every odd row.

downsampleCols :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Downsample an image by discarding every odd column.

downsample Source #

Arguments

:: Array arr cs e 
=> (Int -> Bool)

Rows predicate

-> (Int -> Bool)

Columns predicate

-> Image arr cs e

Source image

-> Image arr cs e 

Downsample an image. Drop all rows and colums that satisfy the predicates. For example, in order to discard every 5th row and keep every even indexed column:

>>> frog <- readImageRGB RPU "images/frog.jpg"
>>> displayImage $ downsample ((0 ==) . (`mod` 5)) odd frog

upsampleRows :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Upsample an image by inserting a row of back pixels after each row of a source image.

upsampleCols :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Upsample an image by inserting a column of back pixels after each column of a source image.

upsample :: Array arr cs e => (Int -> (Int, Int)) -> (Int -> (Int, Int)) -> Image arr cs e -> Image arr cs e Source #

Upsample an image by inserting rows and columns with zero valued pixels into an image. Supplied functions specify how many rows/columns shoud be inserted (before, after) a particular row/column. Returning a negative value in a tuple will result in an error. E.g. insert 2 columns before and 4 columns after every 10th column, while leaving rows count unchanged:

>>> frog <- readImageRGB RPU "images/frog.jpg"
>>> displayImage $ upsample (const (0, 0)) (\ k -> if k `mod` 10 == 0 then (2, 4) else (0, 0)) frog

Concatenation

leftToRight :: Array arr cs e => Image arr cs e -> Image arr cs e -> Image arr cs e Source #

Concatenate two images together into one. Both input images must have the same number of rows.

topToBottom :: Array arr cs e => Image arr cs e -> Image arr cs e -> Image arr cs e Source #

Concatenate two images together into one. Both input images must have the same number of columns.

Canvas

translate Source #

Arguments

:: Array arr cs e 
=> Border (Pixel cs e)

Border resolution strategy

-> (Int, Int)

Number of rows and columns image will be shifted by.

-> Image arr cs e 
-> Image arr cs e 

Shift an image towards its bottom right corner by (delatM, deltaN) rows and columns, while specifying a border resolution strategy.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_translate_wrap.jpg" $ translate Wrap (50, 100) frog
>>> writeImage "images/frog_translate_edge.jpg" $ translate Edge (50, 100) frog

Since: 1.2.0.0

canvasSize Source #

Arguments

:: Array arr cs e 
=> Border (Pixel cs e)

Border resolution strategy

-> (Int, Int)

New dimensions of the image

-> Image arr cs e

Source image

-> Image arr cs e 

Change the size of an image. Pixel values and positions will not change, except the ones outside the border, which are handled according to supplied resolution strategy.

For example, it can be used to make a tile from the image above, or simply scale the canvas and place it in a middle:

>>> logo <- readImageRGBA VU "images/logo_40.png"
>>> let incBy (fm, fn) = (rows logo * fm, cols logo * fn)
>>> writeImage "images/logo_tile.png" $ canvasSize Wrap (incBy (6, 10)) logo
>>> writeImage "images/logo_center.png" $ translate (Fill 0) (incBy (2, 3)) $ canvasSize (Fill 0) (incBy (5, 7)) logo

Since: 1.2.1.0

crop Source #

Arguments

:: Array arr cs e 
=> (Int, Int)

(i, j) starting index from within a source image.

-> (Int, Int)

(m, n) dimensions of a new image.

-> Image arr cs e

Source image.

-> Image arr cs e 

Crop an image, i.e. retrieves a sub-image image with m rows and n columns. Make sure (i + m, j + n) is not greater than dimensions of a source image, otherwise it will result in an error.

superimpose Source #

Arguments

:: Array arr cs e 
=> (Int, Int)

(i, j) starting index from within a source image.

-> Image arr cs e

Image to be positioned above the source image.

-> Image arr cs e

Source image.

-> Image arr cs e 

Place one image on top of a source image, starting at a particular location within a source image.

Flipping

flipV :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Flip an image vertically.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_flipV.jpg" $ flipV frog

flipH :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Flip an image horizontally.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_flipH.jpg" $ flipH frog

Rotation

rotate90 :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Rotate an image clockwise by 90°.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_rotate90.jpg" $ rotate90 frog

rotate180 :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Rotate an image by 180°.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_rotate180.jpg" $ rotate180 frog

rotate270 :: Array arr cs e => Image arr cs e -> Image arr cs e Source #

Rotate an image clockwise by 270°.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_rotate270.jpg" $ rotate270 frog

rotate Source #

Arguments

:: (Array arr cs e, Interpolation method) 
=> method

Interpolation method to be used

-> Border (Pixel cs e)

Border handling strategy

-> Double

Angle in radians

-> Image arr cs e

Source image

-> Image arr cs e

Rotated image

Rotate an image clockwise by an angle Θ in radians.

>>> frog <- readImageRGBA VU "images/frog.jpg"
>>> writeImage "images/frog_rotate330.png" $ rotate Bilinear (Fill 0) (11*pi/6) frog

Scaling

resize Source #

Arguments

:: (Interpolation method, Array arr cs e) 
=> method

Interpolation method to be used during scaling.

-> Border (Pixel cs e)

Border handling strategy

-> (Int, Int)

Dimensions of a result image.

-> Image arr cs e

Source image.

-> Image arr cs e

Result image.

Resize an image using an interpolation method.

>>> frog <- readImageRGB VU "images/frog.jpg"
>>> writeImage "images/frog_resize.jpg" $ resize Bilinear Edge (100, 640) frog

scale Source #

Arguments

:: (Interpolation method, Array arr cs e) 
=> method

Interpolation method to be used during scaling.

-> Border (Pixel cs e)

Border handling strategy

-> (Double, Double)

Positive scaling factors.

-> Image arr cs e

Source image.

-> Image arr cs e 

Scale an image. Same as resize, except scaling factors are supplied instead of new dimensions.

 scale Bilinear Edge (0.5, 2) frog == resize Bilinear Edge (100, 640) frog