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

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

Graphics.Image.Interface

Description

 

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.

csColour :: cs -> AlphaColour Double Source

Get a pure colour representation of a channel.

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

A color space that supports transparency.

Associated Types

type Opaque cs Source

An corresponding 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

opaque :: cs -> Opaque cs Source

Get a corresponding opaque channel type.

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)>

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

Base array like representation for an image.

Associated Types

type Elt arr cs e :: Constraint Source

Required array specific constraints for an array element.

data Image arr cs e Source

Underlying image representation.

Methods

makeImage 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 generating 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 VectorUnboxed RGB (Double): 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.

Instances

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

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

Array representation that is actually has real data stored in memory, hence allowing for image indexing, forcing pixels into computed state etc.

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 = 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 Source 
Array RS cs e => ManifestArray RS cs e Source 
Array RP cs e => ManifestArray RP cs e Source 

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

Array representation that allows computation, which depends on some specific order, consequently making it possible to be computed only sequentially.

Methods

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

Fold an image from the left in a row major order.

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

Fold an image from the right in a row major order.

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

Monading mapping over an image.

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

Monading mapping over an image. Result is discarded.

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

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

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

Array representation that supports mutation.

Associated Types

data MImage st arr cs e Source

Methods

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

Get dimensions of a mutable image.

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

Yield a mutable copy of an image.

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

Yield an immutable copy of an image.

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

Create a mutable image with given dimensions. Pixels are likely uninitialized.

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

Yield the pixel at a given location.

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

Set a pixel at a given location.

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

Swap pixels at given locations.

Instances

class Exchangable arr' arr where Source

Allows for changing an underlying image representation.

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 Source

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

Exchangable VU RS Source

O(1) - Changes to Repa representation.

Exchangable VU RP Source

O(1) - Changes to Repa representation.

Exchangable RS VU Source

O(1) - Changes to Vector representation.

Exchangable RS RP Source

O(1) - Changes computation strategy.

Exchangable RS RD Source

O(1) - Delays manifest array.

Exchangable RP VU Source

O(1) - Changes to Vector representation.

Exchangable RP RS Source

O(1) - Changes computation strategy.

Exchangable RP RD Source

O(1) - Delays manifest array.

Exchangable RD RS Source

Computes delayed array sequentially.

Exchangable RD RP Source

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 borders during various transformations. Whenever a function needs information not only about a pixel of interest, but also about it's neighbours, it will go out of bounds around the image edges, hence is this set of approaches that can be used in such situtation.

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.

class Functor f => Applicative f where

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Methods

pure :: a -> f a

Lift a value.

(<*>) :: f (a -> b) -> f a -> f b infixl 4

Sequential application.

(*>) :: f a -> f b -> f b infixl 4

Sequence actions, discarding the value of the first argument.

(<*) :: f a -> f b -> f a infixl 4

Sequence actions, discarding the value of the second argument.

Instances

Applicative [] 
Applicative IO 
Applicative Q 
Applicative Identity 
Applicative Maybe 
Applicative ZipList 
Applicative STM 
Applicative First 
Applicative Last 
Applicative Tree 
Applicative Seq 
Applicative Vector 
Applicative Min 
Applicative Max 
Applicative First 
Applicative Last 
Applicative Option 
Applicative NonEmpty 
Applicative Id 
Applicative Box 
Applicative Stream 
Applicative ((->) a) 
Applicative (Either e) 
Monoid a => Applicative ((,) a) 
Applicative (ReifiedFold s) 
Applicative (ReifiedGetter s) 
Monoid m => Applicative (Const m) 
Applicative (Fold a) 
Applicative (ST s) 
Representable f => Applicative (Co f) 
Applicative (Parser i) 
Monad m => Applicative (WrappedMonad m) 
Arrow a => Applicative (ArrowMonad a) 
Applicative (Proxy *) 
Applicative m => Applicative (IdentityT m) 
Applicative (State s) 
Alternative f => Applicative (Cofree f) 
Applicative f => Applicative (Yoneda f) 
Applicative f => Applicative (Backwards f)

Apply f-actions in the reverse order.

Applicative m => Applicative (ListT m) 
(Functor m, Monad m) => Applicative (MaybeT m) 
Applicative f => Applicative (Indexing f) 
Applicative f => Applicative (Indexing64 f) 
(Applicative (Rep p), Representable p) => Applicative (Prep p) 
Applicative f => Applicative (Reverse f)

Derived instance.

Monoid a => Applicative (Constant a) 
ColorSpace cs => Applicative (Pixel cs) 
Applicative (Indexed i a) 
Arrow a => Applicative (WrappedArrow a b) 
Applicative f => Applicative (Alt * f) 
Biapplicative p => Applicative (Join * p) 
Applicative w => Applicative (TracedT m w) 
Applicative (Cokleisli w a) 
(Applicative f, Applicative g) => Applicative (Day f g) 
(Applicative f, Applicative g) => Applicative (Compose f g) 
(Functor m, Monad m) => Applicative (ErrorT e m) 
(Monad m, Monoid s) => Applicative (Focusing m s) 
Applicative (k (May s)) => Applicative (FocusingMay k s) 
(Monad m, Monoid r) => Applicative (Effect m r) 
Applicative (ContT r m) 
Applicative m => Applicative (ReaderT r m) 
(Functor m, Monad m) => Applicative (StateT s m) 
(Functor m, Monad m) => Applicative (StateT s m) 
(Functor m, Monad m) => Applicative (ExceptT e m) 
(Monoid w, Applicative m) => Applicative (WriterT w m) 
(Monoid w, Applicative m) => Applicative (WriterT w m) 
Applicative f => Applicative (Star f a) 
Applicative (Costar f a) 
Applicative (Tagged k s) 
(Applicative f, Applicative g) => Applicative (Product f g) 
(Monad m, Monoid s, Monoid w) => Applicative (FocusingWith w m s) 
Applicative (k (s, w)) => Applicative (FocusingPlus w k s) 
Applicative (k (f s)) => Applicative (FocusingOn f k s) 
Applicative (k (Err e s)) => Applicative (FocusingErr e k s) 
(Monoid s, Monoid w, Monad m) => Applicative (EffectRWS w st m s) 
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
Reifies k s (ReifiedApplicative f) => Applicative (ReflectedApplicative k * f s) 

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4

An infix synonym for fmap.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(<$) :: Functor f => forall a b. a -> f b -> f a

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4

A variant of <*> with the arguments reversed.

liftA :: Applicative f => (a -> b) -> f a -> f b

Lift a function to actions. This function may be used as a value for fmap in a Functor instance.

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c

Lift a binary function to actions.

liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d

Lift a ternary function to actions.