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

Safe HaskellNone
LanguageHaskell2010

Graphics.Image.Interface

Synopsis

Documentation

class (Eq cs, Enum cs, Show cs, Typeable cs) => ColorSpace cs where Source

This class has all included color spaces installed into it and is also intended for implementing any other possible custom color spaces. Every instance of this class automatically installs an associated Pixel into Num, Fractional, Floating, Functor, Applicative and Foldable, which in turn make it possible to be used by the rest of the library.

Associated Types

type PixelElt cs e Source

Representation of a pixel, such that it can be an element of any Array. Which is usally a tuple of channels or a channel itself for single channel color spaces.

data Pixel cs e Source

A concrete Pixel representation for a particular color space.

Methods

fromChannel :: e -> Pixel cs e Source

Construt a pixel by replicating a same value among all of the channels.

toElt :: Pixel cs e -> PixelElt cs e Source

Convert a Pixel to a representation suitable for storage as an unboxed element, usually a tuple of channels.

fromElt :: PixelElt cs e -> Pixel cs e Source

Convert from an elemnt representation back to a Pixel.

getPxCh :: Pixel cs e -> cs -> e Source

Retrieve Pixel's channel value

chOp :: (cs -> e' -> e) -> Pixel cs e' -> Pixel cs e Source

Map a channel aware function over all Pixel's channels.

pxOp :: (e' -> e) -> Pixel cs e' -> Pixel cs e Source

Map a function over all Pixel's channels.

chApp :: Pixel cs (e' -> e) -> Pixel cs e' -> Pixel cs e Source

Function application to a Pixel.

pxFoldMap :: Monoid m => (e -> m) -> Pixel cs e -> m Source

A pixel eqiuvalent of foldMap.

class (ColorSpace (Opaque cs), ColorSpace cs) => Alpha cs where Source

Associated Types

type Opaque cs Source

An opaque version of this color space.

Methods

getAlpha :: Pixel cs e -> e Source

Get an alpha channel of a transparant pixel.

addAlpha :: e -> Pixel (Opaque cs) e -> Pixel cs e Source

Add an alpha channel of an opaque pixel.

 addAlpha 0 (PixelHSI 1 2 3) == PixelHSIA 1 2 3 0

dropAlpha :: Pixel cs e -> Pixel (Opaque cs) e Source

Convert a transparent pixel to an opaque one by dropping the alpha channel.

 dropAlpha (PixelRGBA 1 2 3 4) == PixelRGB 1 2 3

class Elevator e where Source

A class with a set of convenient functions that allow for changing precision of channels within pixels, while scaling the values to keep them in an appropriate range.

>>> let rgb = PixelRGB 0.0 0.5 1.0 :: Pixel RGB Double
>>> toWord8 rgb
<RGB:(0|128|255)>

Instances

Elevator Double

Values are scaled to [0.0, 1.0] range.

Elevator Float

Values are scaled to [0.0, 1.0] range.

Elevator Word8

Values are scaled to [0, 255] range.

Elevator Word16

Values are scaled to [0, 65535] range.

Elevator Word32

Values are scaled to [0, 4294967295] range.

Elevator Word64

Values are scaled to [0, 18446744073709551615] range.

class (Show arr, ColorSpace cs, Num (Pixel cs e), Num e, Typeable e, Elt arr cs e) => Array arr cs e where Source

Associated Types

type Elt arr cs e :: Constraint Source

data Image arr cs e Source

Methods

make Source

Arguments

:: (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 genrating function.

singleton :: Pixel cs e -> Image arr cs e Source

Create a singleton image, required for various operations on images with a scalar.

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

Get dimensions of an image.

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

map Source

Arguments

:: 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' 
=> ((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 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 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

traverse Source

Arguments

:: 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 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 :: Image arr cs e -> Image arr cs e Source

Transpose an image

backpermute Source

Arguments

:: (Int, Int)

Dimensions of a result image.

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

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

-> Image arr cs e

Source image.

-> Image arr cs e

Result image.

Backwards permutation of an image.

fromLists :: [[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 VU Y Double
<Image VectorUnboxed Luma: 200x300>

Instances

Elt VU cs e => Array VU cs e 
Elt RS cs e => Array RS cs e 
Elt RP cs e => Array RP cs e 
Elt RD cs e => Array RD cs e 

class Array arr cs e => ManifestArray arr cs e where Source

Methods

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

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

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

deepSeqImage :: Image arr cs e -> a -> a Source

Make sure that an image is fully evaluated.

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

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

fold Source

Arguments

:: (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.

eq :: Eq (Pixel cs e) => Image arr cs e -> Image arr cs e -> Bool Source

Pixelwise equality function of two images. Images are considered distinct if either images' dimensions or at least one pair of corresponding pixels are not the same. Used in defining an in instance for the Eq typeclass.

Instances

Array VU cs e => ManifestArray VU cs e 
Array RS cs e => ManifestArray RS cs e 
Array RP cs e => ManifestArray RP cs e 

class ManifestArray arr cs e => SequentialArray arr cs e where Source

Methods

foldl :: (a -> Pixel cs e -> a) -> a -> Image arr cs e -> a Source

foldr :: (Pixel cs e -> a -> a) -> a -> Image arr cs e -> a Source

mapM :: (Array arr cs' e', Monad m) => (Pixel cs' e' -> m (Pixel cs e)) -> Image arr cs' e' -> m (Image arr cs e) Source

mapM_ :: (Array arr cs' e', Monad m) => (Pixel cs' e' -> m (Pixel cs e)) -> Image arr cs' e' -> m () Source

foldM :: Monad m => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m a Source

foldM_ :: Monad m => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m () Source

Instances

class ManifestArray arr cs e => MutableArray arr cs e where Source

Associated Types

data MImage st arr cs e Source

Methods

mdims :: MImage st arr cs e -> (Int, Int) Source

thaw :: PrimMonad m => Image arr cs e -> m (MImage (PrimState m) arr cs e) Source

freeze :: PrimMonad m => MImage (PrimState m) arr cs e -> m (Image arr cs e) Source

new :: PrimMonad m => (Int, Int) -> m (MImage (PrimState m) arr cs e) Source

read :: PrimMonad m => MImage (PrimState m) arr cs e -> (Int, Int) -> m (Pixel cs e) Source

write :: PrimMonad m => MImage (PrimState m) arr cs e -> (Int, Int) -> Pixel cs e -> m () Source

swap :: PrimMonad m => MImage (PrimState m) arr cs e -> (Int, Int) -> (Int, Int) -> m () Source

Instances

class Exchangable arr' arr where Source

Methods

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.

Instances

Exchangable arr arr

Changing to the same array representation as before is disabled and changeTo will behave simply as an identitity function.

Exchangable VU RS

O(1) - Changes to Repa representation.

Exchangable VU RP

O(1) - Changes to Repa representation.

Exchangable RS VU

O(1) - Changes to Vector representation.

Exchangable RS RP

O(1) - Changes computation strategy.

Exchangable RS RD

O(1) - Delays manifest array.

Exchangable RP VU

O(1) - Changes to Vector representation.

Exchangable RP RS

O(1) - Changes computation strategy.

Exchangable RP RD

O(1) - Delays manifest array.

Exchangable RD RS

Computes delayed array sequentially.

Exchangable RD RP

Computes delayed array in parallel.

defaultIndex :: ManifestArray 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.

maybeIndex :: ManifestArray 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 pixel otherwise.

data Border px Source

Approach to be used near the border during transformations, which, besides a pixel of interest, also use it's neighbors, consequently going out of bounds at the edges of an image.

Constructors

Fill !px

Fill in a constant pixel.

           outside |  Image  | outside
(Fill 0) : 0 0 0 0 | 1 2 3 4 | 0 0 0 0
Wrap

Wrap around from the opposite border of the image.

           outside |  Image  | outside
Wrap :     1 2 3 4 | 1 2 3 4 | 1 2 3 4
Edge

Replicate the pixel at the edge.

           outside |  Image  | outside
Edge :     1 1 1 1 | 1 2 3 4 | 4 4 4 4
Reflect

Mirror like reflection.

           outside |  Image  | outside
Reflect :  4 3 2 1 | 1 2 3 4 | 4 3 2 1
Continue

Also mirror like reflection, but without repeating the edge pixel.

           outside |  Image  | outside
Continue : 1 4 3 2 | 1 2 3 4 | 3 2 1 4

borderIndex Source

Arguments

:: Border (Pixel cs e)

Border handling strategy.

-> (Int, Int)

Image dimensions

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

Image's indexing function.

-> (Int, Int)

(i, j) location of a pixel lookup.

-> Pixel cs e 

Border handling function. If (i, j) location is within bounds, then supplied lookup function will be used, otherwise it will be handled according to a supplied border strategy.