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

Safe HaskellNone
LanguageHaskell2010

Graphics.Image.ColorSpace

Contents

Synopsis

ColorSpace

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

Luma

data Y Source

Luma or brightness, that is usually denoted as Y'.

Constructors

Y 

Instances

Enum Y 
Eq Y 
Show Y 
ColorSpace Y 
ToRGB Y 
ToHSI Y 
Typeable * Y 
Array arr Y Double => Readable [Image arr Y Double] [GIF] 
Array arr Y Word16 => Readable [Image arr Y Word16] [PGM] 
Array arr Y Word8 => Readable [Image arr Y Word8] [PGM] 
Eq e => Eq (Pixel Y e) 
Ord e => Ord (Pixel Y e) 
Show e => Show (Pixel Y e) 
ManifestArray arr Y Double => Writable (Image arr Y Double) TIF 
ManifestArray arr Y Word16 => Writable (Image arr Y Word16) TIF 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) TIF 
ManifestArray arr Y Double => Writable (Image arr Y Double) TGA 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) TGA 
ManifestArray arr Y Double => Writable (Image arr Y Double) PNG 
ManifestArray arr Y Word16 => Writable (Image arr Y Word16) PNG 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) PNG 
ManifestArray arr Y Double => Writable (Image arr Y Double) JPG 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) JPG 
ManifestArray arr Y Double => Writable (Image arr Y Double) HDR 
ManifestArray arr Y Double => Writable (Image arr Y Double) GIF 
ManifestArray arr Y Double => Writable (Image arr Y Double) BMP 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) BMP 
Array arr Y Double => Readable (Image arr Y Double) TIF 
Array arr Y Word16 => Readable (Image arr Y Word16) TIF 
Array arr Y Word8 => Readable (Image arr Y Word8) TIF 
Array arr Y Double => Readable (Image arr Y Double) TGA 
Array arr Y Word8 => Readable (Image arr Y Word8) TGA 
Array arr Y Double => Readable (Image arr Y Double) PNG 
Array arr Y Word16 => Readable (Image arr Y Word16) PNG 
Array arr Y Word8 => Readable (Image arr Y Word8) PNG 
Array arr Y Double => Readable (Image arr Y Double) JPG 
Array arr Y Word8 => Readable (Image arr Y Word8) JPG 
Array arr Y Double => Readable (Image arr Y Double) HDR 
Array arr Y Double => Readable (Image arr Y Double) GIF 
Array arr Y Double => Readable (Image arr Y Double) BMP 
Array arr Y Word8 => Readable (Image arr Y Word8) BMP 
Array arr Y Word16 => Readable (Image arr Y Word16) PGM 
Array arr Y Word8 => Readable (Image arr Y Word8) PGM 
Array arr Y Double => Readable (Image arr Y Double) PPM 
Array arr Y Double => Readable (Image arr Y Double) PGM 
Array arr Y Double => Readable (Image arr Y Double) PBM 
data Pixel Y = PixelY !e 
type PixelElt Y e = e 

data YA Source

Luma with Alpha channel.

Constructors

YA 
AlphaYA 

Instances

Enum YA 
Eq YA 
Show YA 
Alpha YA 
ColorSpace YA 
ToRGBA YA 
ToHSIA YA 
Typeable * YA 
Array arr YA Double => Readable [Image arr YA Double] [GIF] 
Eq e => Eq (Pixel YA e) 
Show e => Show (Pixel YA e) 
ManifestArray arr YA Double => Writable (Image arr YA Double) TIF 
ManifestArray arr YA Word16 => Writable (Image arr YA Word16) TIF 
ManifestArray arr YA Word8 => Writable (Image arr YA Word8) TIF 
ManifestArray arr YA Double => Writable (Image arr YA Double) TGA 
ManifestArray arr YA Double => Writable (Image arr YA Double) PNG 
ManifestArray arr YA Word16 => Writable (Image arr YA Word16) PNG 
ManifestArray arr YA Word8 => Writable (Image arr YA Word8) PNG 
ManifestArray arr YA Double => Writable (Image arr YA Double) JPG 
ManifestArray arr YA Double => Writable (Image arr YA Double) HDR 
ManifestArray arr YA Double => Writable (Image arr YA Double) GIF 
ManifestArray arr YA Double => Writable (Image arr YA Double) BMP 
Array arr YA Double => Readable (Image arr YA Double) TIF 
Array arr YA Word16 => Readable (Image arr YA Word16) TIF 
Array arr YA Word8 => Readable (Image arr YA Word8) TIF 
Array arr YA Double => Readable (Image arr YA Double) TGA 
Array arr YA Double => Readable (Image arr YA Double) PNG 
Array arr YA Word16 => Readable (Image arr YA Word16) PNG 
Array arr YA Word8 => Readable (Image arr YA Word8) PNG 
Array arr YA Double => Readable (Image arr YA Double) JPG 
Array arr YA Word8 => Readable (Image arr YA Word8) JPG 
Array arr YA Double => Readable (Image arr YA Double) HDR 
Array arr YA Double => Readable (Image arr YA Double) GIF 
Array arr YA Double => Readable (Image arr YA Double) BMP 
Array arr YA Double => Readable (Image arr YA Double) PPM 
type Opaque YA = Y 
data Pixel YA = PixelYA !e !e 
type PixelElt YA e = (e, e) 

class ColorSpace cs => ToY cs where Source

Minimal complete definition

toPixelY

Methods

toPixelY :: Pixel cs Double -> Pixel Y Double Source

toImageY :: (Array arr cs Double, Array arr Y Double) => Image arr cs Double -> Image arr Y Double Source

Instances

ToY RGB

Computes Luma: Y' = 0.299 * R' + 0.587 * G' + 0.114 * B'

ToY HSI 
ToY CMYK 
ToY YCbCr 
ToY Gray 

class (ToY (Opaque cs), Alpha cs) => ToYA cs where Source

Minimal complete definition

Nothing

Instances

RGB

data RGB Source

Constructors

RedRGB 
GreenRGB 
BlueRGB 

Instances

Enum RGB 
Eq RGB 
Show RGB 
ColorSpace RGB 
ToY RGB

Computes Luma: Y' = 0.299 * R' + 0.587 * G' + 0.114 * B'

ToHSI RGB 
ToCMYK RGB 
ToYCbCr RGB 
Typeable * RGB 
ManifestArray arr RGB Double => Writable [(GifDelay, Image arr RGB Double)] [GIF] 
ManifestArray arr RGB Word8 => Writable [(GifDelay, Image arr RGB Word8)] [GIF] 
Array arr RGB Double => Readable [Image arr RGB Double] [GIF] 
Array arr RGB Word8 => Readable [Image arr RGB Word8] [GIF] 
Array arr RGB Word16 => Readable [Image arr RGB Word16] [PPM] 
Array arr RGB Word8 => Readable [Image arr RGB Word8] [PPM] 
Eq e => Eq (Pixel RGB e) 
Show e => Show (Pixel RGB e) 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) TIF 
ManifestArray arr RGB Word16 => Writable (Image arr RGB Word16) TIF 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) TIF 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) TGA 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) TGA 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) PNG 
ManifestArray arr RGB Word16 => Writable (Image arr RGB Word16) PNG 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) PNG 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) JPG 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) JPG 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) HDR 
ManifestArray arr RGB Float => Writable (Image arr RGB Float) HDR 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) GIF 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) GIF 
ManifestArray arr RGB Double => Writable (Image arr RGB Double) BMP 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) BMP 
Array arr RGB Double => Readable (Image arr RGB Double) TIF 
Array arr RGB Word16 => Readable (Image arr RGB Word16) TIF 
Array arr RGB Word8 => Readable (Image arr RGB Word8) TIF 
Array arr RGB Double => Readable (Image arr RGB Double) TGA 
Array arr RGB Word8 => Readable (Image arr RGB Word8) TGA 
Array arr RGB Double => Readable (Image arr RGB Double) PNG 
Array arr RGB Word16 => Readable (Image arr RGB Word16) PNG 
Array arr RGB Word8 => Readable (Image arr RGB Word8) PNG 
Array arr RGB Double => Readable (Image arr RGB Double) JPG 
Array arr RGB Word8 => Readable (Image arr RGB Word8) JPG 
Array arr RGB Double => Readable (Image arr RGB Double) HDR 
Array arr RGB Float => Readable (Image arr RGB Float) HDR 
Array arr RGB Double => Readable (Image arr RGB Double) GIF 
Array arr RGB Word8 => Readable (Image arr RGB Word8) GIF 
Array arr RGB Double => Readable (Image arr RGB Double) BMP 
Array arr RGB Word8 => Readable (Image arr RGB Word8) BMP 
Array arr RGB Word16 => Readable (Image arr RGB Word16) PPM 
Array arr RGB Word8 => Readable (Image arr RGB Word8) PPM 
Array arr RGB Double => Readable (Image arr RGB Double) PPM 
data Pixel RGB = PixelRGB !e !e !e 
type PixelElt RGB e = (e, e, e) 

data RGBA Source

Instances

Enum RGBA 
Eq RGBA 
Show RGBA 
Alpha RGBA 
ColorSpace RGBA 
ToYA RGBA 
ToHSIA RGBA 
ToCMYKA RGBA 
ToYCbCrA RGBA 
Typeable * RGBA 
Array arr RGBA Double => Readable [Image arr RGBA Double] [GIF] 
Array arr RGBA Word8 => Readable [Image arr RGBA Word8] [GIF] 
Eq e => Eq (Pixel RGBA e) 
Show e => Show (Pixel RGBA e) 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) TIF 
ManifestArray arr RGBA Word16 => Writable (Image arr RGBA Word16) TIF 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) TIF 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) TGA 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) TGA 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) PNG 
ManifestArray arr RGBA Word16 => Writable (Image arr RGBA Word16) PNG 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) PNG 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) HDR 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) GIF 
ManifestArray arr RGBA Double => Writable (Image arr RGBA Double) BMP 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) BMP 
Array arr RGBA Double => Readable (Image arr RGBA Double) TIF 
Array arr RGBA Word16 => Readable (Image arr RGBA Word16) TIF 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) TIF 
Array arr RGBA Double => Readable (Image arr RGBA Double) TGA 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) TGA 
Array arr RGBA Double => Readable (Image arr RGBA Double) PNG 
Array arr RGBA Word16 => Readable (Image arr RGBA Word16) PNG 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) PNG 
Array arr RGBA Double => Readable (Image arr RGBA Double) JPG 
Array arr RGBA Double => Readable (Image arr RGBA Double) HDR 
Array arr RGBA Double => Readable (Image arr RGBA Double) GIF 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) GIF 
Array arr RGBA Double => Readable (Image arr RGBA Double) BMP 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) BMP 
Array arr RGBA Double => Readable (Image arr RGBA Double) PPM 
type Opaque RGBA = RGB 
data Pixel RGBA = PixelRGBA !e !e !e !e 
type PixelElt RGBA e = (e, e, e, e) 

class ColorSpace cs => ToRGB cs where Source

Minimal complete definition

toPixelRGB

class (ToRGB (Opaque cs), Alpha cs) => ToRGBA cs where Source

Minimal complete definition

Nothing

HSI

data HSI Source

Constructors

HueHSI 
SatHSI 
IntHSI 

Instances

Enum HSI 
Eq HSI 
Show HSI 
ColorSpace HSI 
ToY HSI 
ToRGB HSI 
Typeable * HSI 
Eq e => Eq (Pixel HSI e) 
Show e => Show (Pixel HSI e) 
data Pixel HSI = PixelHSI !e !e !e 
type PixelElt HSI e = (e, e, e) 

data HSIA Source

Constructors

HueHSIA 
SatHSIA 
IntHSIA 
AlphaHSIA 

Instances

Enum HSIA 
Eq HSIA 
Show HSIA 
Alpha HSIA 
ColorSpace HSIA 
ToYA HSIA 
ToRGBA HSIA 
Typeable * HSIA 
Eq e => Eq (Pixel HSIA e) 
Show e => Show (Pixel HSIA e) 
type Opaque HSIA = HSI 
data Pixel HSIA = PixelHSIA !e !e !e !e 
type PixelElt HSIA e = (e, e, e, e) 

class ColorSpace cs => ToHSI cs where Source

Minimal complete definition

toPixelHSI

Instances

class (ToHSI (Opaque cs), Alpha cs) => ToHSIA cs where Source

Minimal complete definition

Nothing

Instances

CMYK

data CMYKA Source

Constructors

CyanCMYKA

Cyan

MagCMYKA

Mahenta

YelCMYKA

Yellow

KeyCMYKA

Key (Black)

AlphaCMYKA

Alpha

Instances

Enum CMYKA 
Eq CMYKA 
Show CMYKA 
Alpha CMYKA 
ColorSpace CMYKA 
ToRGBA CMYKA 
Typeable * CMYKA 
Eq e => Eq (Pixel CMYKA e) 
Show e => Show (Pixel CMYKA e) 
type Opaque CMYKA = CMYK 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e 
type PixelElt CMYKA e = (e, e, e, e, e) 

class ColorSpace cs => ToCMYK cs where Source

Minimal complete definition

toPixelCMYK

Instances

class (ToCMYK (Opaque cs), Alpha cs) => ToCMYKA cs where Source

Minimal complete definition

Nothing

Instances

YCbCr

class ColorSpace cs => ToYCbCr cs where Source

Minimal complete definition

toPixelYCbCr

Instances

class (ToYCbCr (Opaque cs), Alpha cs) => ToYCbCrA cs where Source

Minimal complete definition

Nothing

Instances

Gray

data Gray Source

This is a signgle channel colorspace, that is designed to hold any channel from any other colorspace, hence it is not convertible to and from, but rather is here to allow separation of channels from other multichannel colorspaces. If you are looking for a true grayscale colorspace Y should be used instead.

Constructors

Gray 

Instances

Enum Gray 
Eq Gray 
Show Gray 
ColorSpace Gray 
ToY Gray 
Typeable * Gray 
Eq e => Eq (Pixel Gray e) 
Ord e => Ord (Pixel Gray e) 
Show e => Show (Pixel Gray e) 
data Pixel Gray = PixelGray !e 
type PixelElt Gray e = e 

toGrayImages :: (Array arr cs e, Array arr Gray e) => Image arr cs e -> [Image arr Gray e] Source

Separate an image into a list of images with Gray pixels containing every channel from the source image.

>>> frog <- readImageRGB "images/frog.jpg"
>>> let [frog_red, frog_green, frog_blue] = toGrayImages frog
>>> writeImage "images/frog_red.png" $ toImageY frog_red
>>> writeImage "images/frog_green.jpg" $ toImageY frog_green
>>> writeImage "images/frog_blue.jpg" $ toImageY frog_blue

fromGrayImages :: forall arr cs e. (Array arr Gray e, Array arr cs e) => [Image arr Gray e] -> [cs] -> Image arr cs e Source

Combine a list of images with Gray pixels into an image of any color space, by supplying an order of color space channels.

For example here is a frog with swapped BlueRGB and GreenRGB channels.

>>> writeImage "images/frog_rbg.jpg" $ fromGrayImages [frog_red, frog_green, frog_blue] [RedRGB, BlueRGB, GreenRGB]

It is worth noting though, that separating image channels can be sometimes pretty useful, the same effect as above can be achieved in a much simpler and more efficient way:

 map ((PixelRGB r g b) -> PixelRGB r b g) frog

Binary

data Binary Source

This is a Binary colorspace, pixel's of which can be created using these constructors:

on
Represents value 1 or True. It's a foreground pixel and is displayed in black.
off
Represents value 0 or False. It's a background pixel and is displayed in white.

Note, that values are inverted before writing to or reading from file, since grayscale images represent black as a 0 value and white as 1 on a [0,1] scale.

Binary pixels also behave as binary numbers with a size of 1-bit, for instance:

>>> on + on -- equivalent to: 1 .|. 1
<Binary:(1)>
>>> (on + on) * off -- equivalent to: (1 .|. 1) .&. 0
<Binary:(0)>
>>> (on + on) - on
<Binary:(0)>

data Bit Source

Under the hood, Binary pixels are represented as Word8 that can only take values of 0 or 1.

on :: Pixel Binary Bit Source

Represents value True or 1 in binary. Often also called a foreground pixel of an object.

off :: Pixel Binary Bit Source

Represents value False or 0 in binary. Often also called a background pixel.

isOn :: Pixel Binary Bit -> Bool Source

Test if Pixel's value is on.

isOff :: Pixel Binary Bit -> Bool Source

Test if Pixel's value is off.

fromBool :: Bool -> Pixel Binary Bit Source

Convert a Bool to a PixelBin pixel.

>>> isOn (fromBool True)
True

complement :: Pixel Binary Bit -> Pixel Binary Bit Source

Invert value of a pixel. Equivalent of not for Bool's.

toPixelBinary :: (ColorSpace cs, Eq (Pixel cs e), Num e) => Pixel cs e -> Pixel Binary Bit Source

toImageBinary :: (Array arr cs e, Array arr Binary Bit, Eq (Pixel cs e)) => Image arr cs e -> Image arr Binary Bit Source

Complex

Rectangular form

data Complex a :: * -> *

Complex numbers are an algebraic type.

For a complex number z, abs z is a number with the magnitude of z, but oriented in the positive real direction, whereas signum z has the phase of z, but unit magnitude.

Constructors

!a :+ !a infix 6

forms a complex number from its real and imaginary rectangular components.

Instances

(RealFloat a, Unbox a) => Vector Vector (Complex a) 
(RealFloat a, Unbox a) => MVector MVector (Complex a) 
Eq a => Eq (Complex a) 
RealFloat a => Floating (Complex a) 
RealFloat a => Fractional (Complex a) 
Data a => Data (Complex a) 
RealFloat a => Num (Complex a) 
Read a => Read (Complex a) 
Show a => Show (Complex a) 
(RealFloat a, NFData a) => NFData (Complex a) 
(RealFloat a, Unbox a) => Unbox (Complex a) 
Typeable (* -> *) Complex 
data MVector s (Complex a) = MV_Complex (MVector s (a, a)) 
data Vector (Complex a) = V_Complex (Vector (a, a)) 

(+:) :: ColorSpace cs => Pixel cs e -> Pixel cs e -> Pixel cs (Complex e) infix 6 Source

Constrcut a complex pixel from two pixels representing real and imaginary parts.

 PixelRGB 4 8 6 +: PixelRGB 7 1 1 == PixelRGB (4 :+ 7) (8 :+ 1) (6 :+ 1)

realPart :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source

Extracts the real part of a complex pixel.

imagPart :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source

Extracts the imaginary part of a complex pixel.

Polar form

mkPolar :: (ColorSpace cs, RealFloat e) => Pixel cs e -> Pixel cs e -> Pixel cs (Complex e) Source

Form a complex pixel from polar components of magnitude and phase.

cis :: (ColorSpace cs, RealFloat e) => Pixel cs e -> Pixel cs (Complex e) Source

cis t is a complex pixel with magnitude 1 and phase t (modulo 2*pi).

polar :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> (Pixel cs e, Pixel cs e) Source

The function polar takes a complex pixel and returns a (magnitude, phase) pair of pixels in canonical form: the magnitude is nonnegative, and the phase in the range (-pi, pi]; if the magnitude is zero, then so is the phase.

magnitude :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source

The nonnegative magnitude of a complex pixel.

phase :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source

The phase of a complex pixel, in the range (-pi, pi]. If the magnitude is zero, then so is the phase.

Conjugate

conjugate :: (ColorSpace cs, RealFloat e) => Pixel cs (Complex e) -> Pixel cs (Complex e) Source

The conjugate of a complex pixel.

Re-exports

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.

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

An infix synonym for fmap.

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

data Word8 :: *

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 
Integral Word8 
Num Word8 
Ord Word8 
Read Word8 
Real Word8 
Show Word8 
Ix Word8 
Unpackable Word8

The Word8 instance is just a passthrough, to avoid copying memory twice

JpgEncodable Pixel8 
TiffSaveable Pixel8 
PngSavable Pixel8 
TgaSaveable Pixel8 
BmpEncodable Pixel8 
Pixel Pixel8 
LumaPlaneExtractable Pixel8 
PackeablePixel Pixel8 
Storable Word8 
Bits Word8 
FiniteBits Word8 
NFData Word8 
Prim Word8 
Random Word8 
Elt Word8 
Unbox Word8 
Elevator Word8

Values are scaled to [0, 255] range.

Typeable * Word8 
Decimable Pixel16 Pixel8 
Decimable PixelF Pixel8 
TransparentPixel PixelYA8 Pixel8 
ColorConvertible Pixel8 Pixel16 
ColorConvertible Pixel8 PixelF 
ColorConvertible Pixel8 PixelYA8 
ColorConvertible Pixel8 PixelRGB8 
ColorConvertible Pixel8 PixelRGBA8 
Source B Word8

Read elements from a ByteString.

Vector Vector Word8 
MVector MVector Word8 
Structured B Word8 b 
ManifestArray arr RGB Word8 => Writable [(GifDelay, Image arr RGB Word8)] [GIF] 
Array arr RGBA Word8 => Readable [Image arr RGBA Word8] [GIF] 
Array arr RGB Word8 => Readable [Image arr RGB Word8] [GIF] 
Array arr RGB Word8 => Readable [Image arr RGB Word8] [PPM] 
Array arr Y Word8 => Readable [Image arr Y Word8] [PGM] 
Read sh => Read (Array B sh Word8) 
Show sh => Show (Array B sh Word8) 
ManifestArray arr CMYK Word8 => Writable (Image arr CMYK Word8) TIF 
ManifestArray arr YCbCr Word8 => Writable (Image arr YCbCr Word8) TIF 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) TIF 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) TIF 
ManifestArray arr YA Word8 => Writable (Image arr YA Word8) TIF 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) TIF 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) TGA 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) TGA 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) TGA 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) PNG 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) PNG 
ManifestArray arr YA Word8 => Writable (Image arr YA Word8) PNG 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) PNG 
ManifestArray arr YCbCr Word8 => Writable (Image arr YCbCr Word8) JPG 
ManifestArray arr CMYK Word8 => Writable (Image arr CMYK Word8) JPG 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) JPG 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) JPG 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) GIF 
ManifestArray arr RGBA Word8 => Writable (Image arr RGBA Word8) BMP 
ManifestArray arr RGB Word8 => Writable (Image arr RGB Word8) BMP 
ManifestArray arr Y Word8 => Writable (Image arr Y Word8) BMP 
Array arr CMYK Word8 => Readable (Image arr CMYK Word8) TIF 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) TIF 
Array arr RGB Word8 => Readable (Image arr RGB Word8) TIF 
Array arr YA Word8 => Readable (Image arr YA Word8) TIF 
Array arr Y Word8 => Readable (Image arr Y Word8) TIF 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) TGA 
Array arr RGB Word8 => Readable (Image arr RGB Word8) TGA 
Array arr Y Word8 => Readable (Image arr Y Word8) TGA 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) PNG 
Array arr RGB Word8 => Readable (Image arr RGB Word8) PNG 
Array arr YA Word8 => Readable (Image arr YA Word8) PNG 
Array arr Y Word8 => Readable (Image arr Y Word8) PNG 
Array arr YCbCr Word8 => Readable (Image arr YCbCr Word8) JPG 
Array arr CMYK Word8 => Readable (Image arr CMYK Word8) JPG 
Array arr RGB Word8 => Readable (Image arr RGB Word8) JPG 
Array arr YA Word8 => Readable (Image arr YA Word8) JPG 
Array arr Y Word8 => Readable (Image arr Y Word8) JPG 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) GIF 
Array arr RGB Word8 => Readable (Image arr RGB Word8) GIF 
Array arr RGBA Word8 => Readable (Image arr RGBA Word8) BMP 
Array arr RGB Word8 => Readable (Image arr RGB Word8) BMP 
Array arr Y Word8 => Readable (Image arr Y Word8) BMP 
Array arr RGB Word8 => Readable (Image arr RGB Word8) PPM 
Array arr Y Word8 => Readable (Image arr Y Word8) PGM 
type StorageType Word8 = Word8 
type PixelBaseComponent Pixel8 = Word8 
type PackedRepresentation Pixel8 = Pixel8 
data Vector Word8 = V_Word8 (Vector Word8) 
data MVector s Word8 = MV_Word8 (MVector s Word8) 
data Array B sh Word8 = AByteString !sh !ByteString 

data Word16 :: *

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 
Integral Word16 
Num Word16 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
Unpackable Word16 
TiffSaveable Pixel16 
PngSavable Pixel16 
Pixel Pixel16 
LumaPlaneExtractable Pixel16 
PackeablePixel Pixel16 
Storable Word16 
Bits Word16 
FiniteBits Word16 
NFData Word16 
Prim Word16 
Random Word16 
Elt Word16 
Unbox Word16 
Elevator Word16

Values are scaled to [0, 65535] range.

Typeable * Word16 
Decimable Pixel16 Pixel8 
BinaryParam Endianness Word16 
TransparentPixel PixelYA16 Pixel16 
ColorConvertible Pixel8 Pixel16 
ColorConvertible Pixel16 PixelYA16 
ColorConvertible Pixel16 PixelRGB16 
ColorConvertible Pixel16 PixelRGBA16 
Vector Vector Word16 
MVector MVector Word16 
Array arr RGB Word16 => Readable [Image arr RGB Word16] [PPM] 
Array arr Y Word16 => Readable [Image arr Y Word16] [PGM] 
ManifestArray arr CMYK Word16 => Writable (Image arr CMYK Word16) TIF 
ManifestArray arr RGBA Word16 => Writable (Image arr RGBA Word16) TIF 
ManifestArray arr RGB Word16 => Writable (Image arr RGB Word16) TIF 
ManifestArray arr YA Word16 => Writable (Image arr YA Word16) TIF 
ManifestArray arr Y Word16 => Writable (Image arr Y Word16) TIF 
ManifestArray arr RGBA Word16 => Writable (Image arr RGBA Word16) PNG 
ManifestArray arr RGB Word16 => Writable (Image arr RGB Word16) PNG 
ManifestArray arr YA Word16 => Writable (Image arr YA Word16) PNG 
ManifestArray arr Y Word16 => Writable (Image arr Y Word16) PNG 
Array arr CMYK Word16 => Readable (Image arr CMYK Word16) TIF 
Array arr RGBA Word16 => Readable (Image arr RGBA Word16) TIF 
Array arr RGB Word16 => Readable (Image arr RGB Word16) TIF 
Array arr YA Word16 => Readable (Image arr YA Word16) TIF 
Array arr Y Word16 => Readable (Image arr Y Word16) TIF 
Array arr RGBA Word16 => Readable (Image arr RGBA Word16) PNG 
Array arr RGB Word16 => Readable (Image arr RGB Word16) PNG 
Array arr YA Word16 => Readable (Image arr YA Word16) PNG 
Array arr Y Word16 => Readable (Image arr Y Word16) PNG 
Array arr RGB Word16 => Readable (Image arr RGB Word16) PPM 
Array arr Y Word16 => Readable (Image arr Y Word16) PGM 
type StorageType Word16 = Word16 
type PixelBaseComponent Pixel16 = Word16 
type PackedRepresentation Pixel16 = Pixel16 
data Vector Word16 = V_Word16 (Vector Word16) 
data MVector s Word16 = MV_Word16 (MVector s Word16)