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

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

Graphics.Image.ColorSpace

Contents

Description

 

Synopsis

ColorSpace

class (Eq cs, Enum cs, Show cs, Typeable cs, Elevator e, Typeable e) => ColorSpace cs e Source #

Instances

(Elevator e, Typeable * e) => ColorSpace YCbCrA e Source # 

Associated Types

type Components YCbCrA e :: * Source #

Methods

toComponents :: Pixel YCbCrA e -> Components YCbCrA e Source #

fromComponents :: Components YCbCrA e -> Pixel YCbCrA e Source #

broadcastC :: e -> Pixel YCbCrA e Source #

getPxC :: Pixel YCbCrA e -> YCbCrA -> e Source #

setPxC :: Pixel YCbCrA e -> YCbCrA -> e -> Pixel YCbCrA e Source #

mapPxC :: (YCbCrA -> e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

mapPx :: (e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

zipWithPx :: (e -> e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YCbCrA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YCbCrA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YCbCrA e -> e Source #

toListPx :: Pixel YCbCrA e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace YCbCr e Source # 

Associated Types

type Components YCbCr e :: * Source #

Methods

toComponents :: Pixel YCbCr e -> Components YCbCr e Source #

fromComponents :: Components YCbCr e -> Pixel YCbCr e Source #

broadcastC :: e -> Pixel YCbCr e Source #

getPxC :: Pixel YCbCr e -> YCbCr -> e Source #

setPxC :: Pixel YCbCr e -> YCbCr -> e -> Pixel YCbCr e Source #

mapPxC :: (YCbCr -> e -> e) -> Pixel YCbCr e -> Pixel YCbCr e Source #

mapPx :: (e -> e) -> Pixel YCbCr e -> Pixel YCbCr e Source #

zipWithPx :: (e -> e -> e) -> Pixel YCbCr e -> Pixel YCbCr e -> Pixel YCbCr e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YCbCr e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YCbCr e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YCbCr e -> e Source #

toListPx :: Pixel YCbCr e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace RGBA e Source # 

Associated Types

type Components RGBA e :: * Source #

Methods

toComponents :: Pixel RGBA e -> Components RGBA e Source #

fromComponents :: Components RGBA e -> Pixel RGBA e Source #

broadcastC :: e -> Pixel RGBA e Source #

getPxC :: Pixel RGBA e -> RGBA -> e Source #

setPxC :: Pixel RGBA e -> RGBA -> e -> Pixel RGBA e Source #

mapPxC :: (RGBA -> e -> e) -> Pixel RGBA e -> Pixel RGBA e Source #

mapPx :: (e -> e) -> Pixel RGBA e -> Pixel RGBA e Source #

zipWithPx :: (e -> e -> e) -> Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel RGBA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel RGBA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel RGBA e -> e Source #

toListPx :: Pixel RGBA e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace RGB e Source # 

Associated Types

type Components RGB e :: * Source #

Methods

toComponents :: Pixel RGB e -> Components RGB e Source #

fromComponents :: Components RGB e -> Pixel RGB e Source #

broadcastC :: e -> Pixel RGB e Source #

getPxC :: Pixel RGB e -> RGB -> e Source #

setPxC :: Pixel RGB e -> RGB -> e -> Pixel RGB e Source #

mapPxC :: (RGB -> e -> e) -> Pixel RGB e -> Pixel RGB e Source #

mapPx :: (e -> e) -> Pixel RGB e -> Pixel RGB e Source #

zipWithPx :: (e -> e -> e) -> Pixel RGB e -> Pixel RGB e -> Pixel RGB e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel RGB e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel RGB e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel RGB e -> e Source #

toListPx :: Pixel RGB e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace YA e Source # 

Associated Types

type Components YA e :: * Source #

Methods

toComponents :: Pixel YA e -> Components YA e Source #

fromComponents :: Components YA e -> Pixel YA e Source #

broadcastC :: e -> Pixel YA e Source #

getPxC :: Pixel YA e -> YA -> e Source #

setPxC :: Pixel YA e -> YA -> e -> Pixel YA e Source #

mapPxC :: (YA -> e -> e) -> Pixel YA e -> Pixel YA e Source #

mapPx :: (e -> e) -> Pixel YA e -> Pixel YA e Source #

zipWithPx :: (e -> e -> e) -> Pixel YA e -> Pixel YA e -> Pixel YA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YA e -> e Source #

toListPx :: Pixel YA e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace Y e Source # 

Associated Types

type Components Y e :: * Source #

Methods

toComponents :: Pixel Y e -> Components Y e Source #

fromComponents :: Components Y e -> Pixel Y e Source #

broadcastC :: e -> Pixel Y e Source #

getPxC :: Pixel Y e -> Y -> e Source #

setPxC :: Pixel Y e -> Y -> e -> Pixel Y e Source #

mapPxC :: (Y -> e -> e) -> Pixel Y e -> Pixel Y e Source #

mapPx :: (e -> e) -> Pixel Y e -> Pixel Y e Source #

zipWithPx :: (e -> e -> e) -> Pixel Y e -> Pixel Y e -> Pixel Y e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel Y e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel Y e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel Y e -> e Source #

toListPx :: Pixel Y e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace HSIA e Source # 

Associated Types

type Components HSIA e :: * Source #

Methods

toComponents :: Pixel HSIA e -> Components HSIA e Source #

fromComponents :: Components HSIA e -> Pixel HSIA e Source #

broadcastC :: e -> Pixel HSIA e Source #

getPxC :: Pixel HSIA e -> HSIA -> e Source #

setPxC :: Pixel HSIA e -> HSIA -> e -> Pixel HSIA e Source #

mapPxC :: (HSIA -> e -> e) -> Pixel HSIA e -> Pixel HSIA e Source #

mapPx :: (e -> e) -> Pixel HSIA e -> Pixel HSIA e Source #

zipWithPx :: (e -> e -> e) -> Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel HSIA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel HSIA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel HSIA e -> e Source #

toListPx :: Pixel HSIA e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace HSI e Source # 

Associated Types

type Components HSI e :: * Source #

Methods

toComponents :: Pixel HSI e -> Components HSI e Source #

fromComponents :: Components HSI e -> Pixel HSI e Source #

broadcastC :: e -> Pixel HSI e Source #

getPxC :: Pixel HSI e -> HSI -> e Source #

setPxC :: Pixel HSI e -> HSI -> e -> Pixel HSI e Source #

mapPxC :: (HSI -> e -> e) -> Pixel HSI e -> Pixel HSI e Source #

mapPx :: (e -> e) -> Pixel HSI e -> Pixel HSI e Source #

zipWithPx :: (e -> e -> e) -> Pixel HSI e -> Pixel HSI e -> Pixel HSI e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel HSI e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel HSI e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel HSI e -> e Source #

toListPx :: Pixel HSI e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace Gray e Source # 

Associated Types

type Components Gray e :: * Source #

Methods

toComponents :: Pixel Gray e -> Components Gray e Source #

fromComponents :: Components Gray e -> Pixel Gray e Source #

broadcastC :: e -> Pixel Gray e Source #

getPxC :: Pixel Gray e -> Gray -> e Source #

setPxC :: Pixel Gray e -> Gray -> e -> Pixel Gray e Source #

mapPxC :: (Gray -> e -> e) -> Pixel Gray e -> Pixel Gray e Source #

mapPx :: (e -> e) -> Pixel Gray e -> Pixel Gray e Source #

zipWithPx :: (e -> e -> e) -> Pixel Gray e -> Pixel Gray e -> Pixel Gray e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel Gray e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel Gray e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel Gray e -> e Source #

toListPx :: Pixel Gray e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace CMYKA e Source # 

Associated Types

type Components CMYKA e :: * Source #

Methods

toComponents :: Pixel CMYKA e -> Components CMYKA e Source #

fromComponents :: Components CMYKA e -> Pixel CMYKA e Source #

broadcastC :: e -> Pixel CMYKA e Source #

getPxC :: Pixel CMYKA e -> CMYKA -> e Source #

setPxC :: Pixel CMYKA e -> CMYKA -> e -> Pixel CMYKA e Source #

mapPxC :: (CMYKA -> e -> e) -> Pixel CMYKA e -> Pixel CMYKA e Source #

mapPx :: (e -> e) -> Pixel CMYKA e -> Pixel CMYKA e Source #

zipWithPx :: (e -> e -> e) -> Pixel CMYKA e -> Pixel CMYKA e -> Pixel CMYKA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel CMYKA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel CMYKA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel CMYKA e -> e Source #

toListPx :: Pixel CMYKA e -> [e] Source #

(Elevator e, Typeable * e) => ColorSpace CMYK e Source # 

Associated Types

type Components CMYK e :: * Source #

Methods

toComponents :: Pixel CMYK e -> Components CMYK e Source #

fromComponents :: Components CMYK e -> Pixel CMYK e Source #

broadcastC :: e -> Pixel CMYK e Source #

getPxC :: Pixel CMYK e -> CMYK -> e Source #

setPxC :: Pixel CMYK e -> CMYK -> e -> Pixel CMYK e Source #

mapPxC :: (CMYK -> e -> e) -> Pixel CMYK e -> Pixel CMYK e Source #

mapPx :: (e -> e) -> Pixel CMYK e -> Pixel CMYK e Source #

zipWithPx :: (e -> e -> e) -> Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel CMYK e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel CMYK e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel CMYK e -> e Source #

toListPx :: Pixel CMYK e -> [e] Source #

ColorSpace Binary Bit Source # 

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class (ColorSpace (Opaque cs) e, ColorSpace cs e) => AlphaSpace cs e where Source #

A color space that supports transparency.

Minimal complete definition

getAlpha, addAlpha, dropAlpha

Associated Types

type Opaque cs Source #

A 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

Instances

(Elevator e, Typeable * e) => AlphaSpace YCbCrA e Source # 

Associated Types

type Opaque YCbCrA :: * Source #

(Elevator e, Typeable * e) => AlphaSpace RGBA e Source # 

Associated Types

type Opaque RGBA :: * Source #

(Elevator e, Typeable * e) => AlphaSpace YA e Source # 

Associated Types

type Opaque YA :: * Source #

Methods

getAlpha :: Pixel YA e -> e Source #

addAlpha :: e -> Pixel (Opaque YA) e -> Pixel YA e Source #

dropAlpha :: Pixel YA e -> Pixel (Opaque YA) e Source #

(Elevator e, Typeable * e) => AlphaSpace HSIA e Source # 

Associated Types

type Opaque HSIA :: * Source #

(Elevator e, Typeable * e) => AlphaSpace CMYKA e Source # 

Associated Types

type Opaque CMYKA :: * Source #

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

Minimal complete definition

toWord8, toWord16, toWord32, toWord64, toFloat, toDouble, fromDouble

Methods

toWord8 :: e -> Word8 Source #

Values are scaled to [0, 255] range.

toWord16 :: e -> Word16 Source #

Values are scaled to [0, 65535] range.

toWord32 :: e -> Word32 Source #

Values are scaled to [0, 4294967295] range.

toWord64 :: e -> Word64 Source #

Values are scaled to [0, 18446744073709551615] range.

toFloat :: e -> Float Source #

Values are scaled to [0.0, 1.0] range.

toDouble :: e -> Double Source #

Values are scaled to [0.0, 1.0] range.

fromDouble :: Double -> e Source #

Values are scaled from [0.0, 1.0] range.

Luma

data Y Source #

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

Constructors

LumaY 

Instances

Enum Y Source # 

Methods

succ :: Y -> Y #

pred :: Y -> Y #

toEnum :: Int -> Y #

fromEnum :: Y -> Int #

enumFrom :: Y -> [Y] #

enumFromThen :: Y -> Y -> [Y] #

enumFromTo :: Y -> Y -> [Y] #

enumFromThenTo :: Y -> Y -> Y -> [Y] #

Eq Y Source # 

Methods

(==) :: Y -> Y -> Bool #

(/=) :: Y -> Y -> Bool #

Show Y Source # 

Methods

showsPrec :: Int -> Y -> ShowS #

show :: Y -> String #

showList :: [Y] -> ShowS #

ChannelColour Y Source # 
(Elevator e, Typeable * e) => ColorSpace Y e Source # 

Associated Types

type Components Y e :: * Source #

Methods

toComponents :: Pixel Y e -> Components Y e Source #

fromComponents :: Components Y e -> Pixel Y e Source #

broadcastC :: e -> Pixel Y e Source #

getPxC :: Pixel Y e -> Y -> e Source #

setPxC :: Pixel Y e -> Y -> e -> Pixel Y e Source #

mapPxC :: (Y -> e -> e) -> Pixel Y e -> Pixel Y e Source #

mapPx :: (e -> e) -> Pixel Y e -> Pixel Y e Source #

zipWithPx :: (e -> e -> e) -> Pixel Y e -> Pixel Y e -> Pixel Y e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel Y e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel Y e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel Y e -> e Source #

toListPx :: Pixel Y e -> [e] Source #

Monad (Pixel Y) Source # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Functor (Pixel Y) Source # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel Y) Source # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Foldable (Pixel Y) Source # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Array arr Y Double => Readable [Image arr Y Double] [GIF] Source # 
Readable [Image VS Y Word8] [PGM] Source # 
Readable [Image VS Y Word16] [PGM] Source # 
Eq e => Eq (Pixel Y e) Source # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Floating e => Floating (Pixel Y e) Source # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Fractional e => Fractional (Pixel Y e) Source # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Num e => Num (Pixel Y e) Source # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Ord e => Ord (Pixel Y e) Source # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Show e => Show (Pixel Y e) Source # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Storable e => Storable (Pixel Y e) Source # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Writable (Image VS Y Double) TIF Source # 
Writable (Image VS Y Double) TGA Source # 
Writable (Image VS Y Double) PNG Source # 
Writable (Image VS Y Double) JPG Source # 
Writable (Image VS Y Double) HDR Source # 
Writable (Image VS Y Double) GIF Source # 
Writable (Image VS Y Double) BMP Source # 
Writable (Image VS Y Word8) TIF Source # 
Writable (Image VS Y Word8) TGA Source # 
Writable (Image VS Y Word8) PNG Source # 
Writable (Image VS Y Word8) JPG Source # 
Writable (Image VS Y Word8) BMP Source # 
Writable (Image VS Y Word16) TIF Source # 
Writable (Image VS Y Word16) PNG Source # 
Array arr Y Double => Readable (Image arr Y Double) TIF Source # 
Array arr Y Double => Readable (Image arr Y Double) TGA Source # 
Array arr Y Double => Readable (Image arr Y Double) PNG Source # 
Array arr Y Double => Readable (Image arr Y Double) JPG Source # 
Array arr Y Double => Readable (Image arr Y Double) HDR Source # 
Array arr Y Double => Readable (Image arr Y Double) GIF Source # 
Array arr Y Double => Readable (Image arr Y Double) BMP Source # 
Array arr Y Double => Readable (Image arr Y Double) PPM Source # 
Array arr Y Double => Readable (Image arr Y Double) PGM Source # 
Array arr Y Double => Readable (Image arr Y Double) PBM Source # 
Readable (Image VS Y Word8) TIF Source # 
Readable (Image VS Y Word8) TGA Source # 
Readable (Image VS Y Word8) PNG Source # 
Readable (Image VS Y Word8) JPG Source # 
Readable (Image VS Y Word8) BMP Source # 
Readable (Image VS Y Word8) PGM Source # 
Readable (Image VS Y Word16) TIF Source # 
Readable (Image VS Y Word16) PNG Source # 
Readable (Image VS Y Word16) PGM Source # 
data Pixel Y Source # 
data Pixel Y = PixelY !e
type Components Y e Source # 
type Components Y e = e

data YA Source #

Luma with Alpha channel.

Constructors

LumaYA

Luma

AlphaYA

Alpha channel

Instances

Enum YA Source # 

Methods

succ :: YA -> YA #

pred :: YA -> YA #

toEnum :: Int -> YA #

fromEnum :: YA -> Int #

enumFrom :: YA -> [YA] #

enumFromThen :: YA -> YA -> [YA] #

enumFromTo :: YA -> YA -> [YA] #

enumFromThenTo :: YA -> YA -> YA -> [YA] #

Eq YA Source # 

Methods

(==) :: YA -> YA -> Bool #

(/=) :: YA -> YA -> Bool #

Show YA Source # 

Methods

showsPrec :: Int -> YA -> ShowS #

show :: YA -> String #

showList :: [YA] -> ShowS #

ChannelColour YA Source # 
(Elevator e, Typeable * e) => AlphaSpace YA e Source # 

Associated Types

type Opaque YA :: * Source #

Methods

getAlpha :: Pixel YA e -> e Source #

addAlpha :: e -> Pixel (Opaque YA) e -> Pixel YA e Source #

dropAlpha :: Pixel YA e -> Pixel (Opaque YA) e Source #

(Elevator e, Typeable * e) => ColorSpace YA e Source # 

Associated Types

type Components YA e :: * Source #

Methods

toComponents :: Pixel YA e -> Components YA e Source #

fromComponents :: Components YA e -> Pixel YA e Source #

broadcastC :: e -> Pixel YA e Source #

getPxC :: Pixel YA e -> YA -> e Source #

setPxC :: Pixel YA e -> YA -> e -> Pixel YA e Source #

mapPxC :: (YA -> e -> e) -> Pixel YA e -> Pixel YA e Source #

mapPx :: (e -> e) -> Pixel YA e -> Pixel YA e Source #

zipWithPx :: (e -> e -> e) -> Pixel YA e -> Pixel YA e -> Pixel YA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YA e -> e Source #

toListPx :: Pixel YA e -> [e] Source #

Functor (Pixel YA) Source # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel YA) Source # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Foldable (Pixel YA) Source # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Array arr YA Double => Readable [Image arr YA Double] [GIF] Source # 
Eq e => Eq (Pixel YA e) Source # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Floating e => Floating (Pixel YA e) Source # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Fractional e => Fractional (Pixel YA e) Source # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Num e => Num (Pixel YA e) Source # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Storable e => Storable (Pixel YA e) Source # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Writable (Image VS YA Double) TIF Source # 
Writable (Image VS YA Double) TGA Source # 
Writable (Image VS YA Double) PNG Source # 
Writable (Image VS YA Double) JPG Source # 
Writable (Image VS YA Double) HDR Source # 
Writable (Image VS YA Double) GIF Source # 
Writable (Image VS YA Double) BMP Source # 
Writable (Image VS YA Word8) TIF Source # 
Writable (Image VS YA Word8) PNG Source # 
Writable (Image VS YA Word16) TIF Source # 
Writable (Image VS YA Word16) PNG Source # 
Array arr YA Double => Readable (Image arr YA Double) TIF Source # 
Array arr YA Double => Readable (Image arr YA Double) TGA Source # 
Array arr YA Double => Readable (Image arr YA Double) PNG Source # 
Array arr YA Double => Readable (Image arr YA Double) JPG Source # 
Array arr YA Double => Readable (Image arr YA Double) HDR Source # 
Array arr YA Double => Readable (Image arr YA Double) GIF Source # 
Array arr YA Double => Readable (Image arr YA Double) BMP Source # 
Array arr YA Double => Readable (Image arr YA Double) PPM Source # 
Readable (Image VS YA Word8) TIF Source # 
Readable (Image VS YA Word8) PNG Source # 
Readable (Image VS YA Word8) JPG Source # 
Readable (Image VS YA Word16) TIF Source # 
Readable (Image VS YA Word16) PNG Source # 
type Opaque YA Source # 
type Opaque YA = Y
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
type Components YA e Source # 
type Components YA e = (e, e)

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class ColorSpace cs Double => ToY cs where Source #

Conversion to Luma color space.

Minimal complete definition

toPixelY

Methods

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

Convert a pixel to Luma pixel.

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

Convert an image to Luma image.

class (ToY (Opaque cs), AlphaSpace cs Double) => ToYA cs where Source #

Conversion to Luma from another color space with Alpha channel.

Methods

toPixelYA :: Pixel cs Double -> Pixel YA Double Source #

Convert a pixel to Luma pixel with Alpha.

toImageYA :: (Array arr cs Double, Array arr YA Double) => Image arr cs Double -> Image arr YA Double Source #

Convert an image to Luma image with Alpha.

RGB

data RGB Source #

Red, Green and Blue color space.

Constructors

RedRGB 
GreenRGB 
BlueRGB 

Instances

Enum RGB Source # 

Methods

succ :: RGB -> RGB #

pred :: RGB -> RGB #

toEnum :: Int -> RGB #

fromEnum :: RGB -> Int #

enumFrom :: RGB -> [RGB] #

enumFromThen :: RGB -> RGB -> [RGB] #

enumFromTo :: RGB -> RGB -> [RGB] #

enumFromThenTo :: RGB -> RGB -> RGB -> [RGB] #

Eq RGB Source # 

Methods

(==) :: RGB -> RGB -> Bool #

(/=) :: RGB -> RGB -> Bool #

Show RGB Source # 

Methods

showsPrec :: Int -> RGB -> ShowS #

show :: RGB -> String #

showList :: [RGB] -> ShowS #

ChannelColour RGB Source # 
(Elevator e, Typeable * e) => ColorSpace RGB e Source # 

Associated Types

type Components RGB e :: * Source #

Methods

toComponents :: Pixel RGB e -> Components RGB e Source #

fromComponents :: Components RGB e -> Pixel RGB e Source #

broadcastC :: e -> Pixel RGB e Source #

getPxC :: Pixel RGB e -> RGB -> e Source #

setPxC :: Pixel RGB e -> RGB -> e -> Pixel RGB e Source #

mapPxC :: (RGB -> e -> e) -> Pixel RGB e -> Pixel RGB e Source #

mapPx :: (e -> e) -> Pixel RGB e -> Pixel RGB e Source #

zipWithPx :: (e -> e -> e) -> Pixel RGB e -> Pixel RGB e -> Pixel RGB e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel RGB e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel RGB e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel RGB e -> e Source #

toListPx :: Pixel RGB e -> [e] Source #

Functor (Pixel RGB) Source # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel RGB) Source # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Foldable (Pixel RGB) Source # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Writable [(GifDelay, Image VS RGB Double)] [GIF] Source # 
Writable [(GifDelay, Image VS RGB Word8)] [GIF] Source # 
Array arr RGB Double => Readable [Image arr RGB Double] [GIF] Source # 
Readable [Image VS RGB Word8] [GIF] Source # 
Readable [Image VS RGB Word8] [PPM] Source # 
Readable [Image VS RGB Word16] [PPM] Source # 
Eq e => Eq (Pixel RGB e) Source # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Floating e => Floating (Pixel RGB e) Source # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Fractional e => Fractional (Pixel RGB e) Source # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Num e => Num (Pixel RGB e) Source # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Show e => Show (Pixel RGB e) Source # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Storable e => Storable (Pixel RGB e) Source # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Writable (Image VS RGB Double) TIF Source # 
Writable (Image VS RGB Double) TGA Source # 
Writable (Image VS RGB Double) PNG Source # 
Writable (Image VS RGB Double) JPG Source # 
Writable (Image VS RGB Double) HDR Source # 
Writable (Image VS RGB Double) GIF Source # 
Writable (Image VS RGB Double) BMP Source # 
Writable (Image VS RGB Float) HDR Source # 
Writable (Image VS RGB Word8) TIF Source # 
Writable (Image VS RGB Word8) TGA Source # 
Writable (Image VS RGB Word8) PNG Source # 
Writable (Image VS RGB Word8) JPG Source # 
Writable (Image VS RGB Word8) GIF Source # 
Writable (Image VS RGB Word8) BMP Source # 
Writable (Image VS RGB Word16) TIF Source # 
Writable (Image VS RGB Word16) PNG Source # 
Array arr RGB Double => Readable (Image arr RGB Double) TIF Source # 
Array arr RGB Double => Readable (Image arr RGB Double) TGA Source # 
Array arr RGB Double => Readable (Image arr RGB Double) PNG Source # 
Array arr RGB Double => Readable (Image arr RGB Double) JPG Source # 
Array arr RGB Double => Readable (Image arr RGB Double) HDR Source # 
Array arr RGB Double => Readable (Image arr RGB Double) GIF Source # 
Array arr RGB Double => Readable (Image arr RGB Double) BMP Source # 
Array arr RGB Double => Readable (Image arr RGB Double) PPM Source # 
Readable (Image VS RGB Float) HDR Source # 
Readable (Image VS RGB Word8) TIF Source # 
Readable (Image VS RGB Word8) TGA Source # 
Readable (Image VS RGB Word8) PNG Source # 
Readable (Image VS RGB Word8) JPG Source # 
Readable (Image VS RGB Word8) GIF Source # 
Readable (Image VS RGB Word8) BMP Source # 
Readable (Image VS RGB Word8) PPM Source # 
Readable (Image VS RGB Word16) TIF Source # 
Readable (Image VS RGB Word16) PNG Source # 
Readable (Image VS RGB Word16) PPM Source # 
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
type Components RGB e Source # 
type Components RGB e = (e, e, e)

data RGBA Source #

Red, Green and Blue color space with Alpha channel.

Instances

Enum RGBA Source # 

Methods

succ :: RGBA -> RGBA #

pred :: RGBA -> RGBA #

toEnum :: Int -> RGBA #

fromEnum :: RGBA -> Int #

enumFrom :: RGBA -> [RGBA] #

enumFromThen :: RGBA -> RGBA -> [RGBA] #

enumFromTo :: RGBA -> RGBA -> [RGBA] #

enumFromThenTo :: RGBA -> RGBA -> RGBA -> [RGBA] #

Eq RGBA Source # 

Methods

(==) :: RGBA -> RGBA -> Bool #

(/=) :: RGBA -> RGBA -> Bool #

Show RGBA Source # 

Methods

showsPrec :: Int -> RGBA -> ShowS #

show :: RGBA -> String #

showList :: [RGBA] -> ShowS #

ChannelColour RGBA Source # 
(Elevator e, Typeable * e) => AlphaSpace RGBA e Source # 

Associated Types

type Opaque RGBA :: * Source #

(Elevator e, Typeable * e) => ColorSpace RGBA e Source # 

Associated Types

type Components RGBA e :: * Source #

Methods

toComponents :: Pixel RGBA e -> Components RGBA e Source #

fromComponents :: Components RGBA e -> Pixel RGBA e Source #

broadcastC :: e -> Pixel RGBA e Source #

getPxC :: Pixel RGBA e -> RGBA -> e Source #

setPxC :: Pixel RGBA e -> RGBA -> e -> Pixel RGBA e Source #

mapPxC :: (RGBA -> e -> e) -> Pixel RGBA e -> Pixel RGBA e Source #

mapPx :: (e -> e) -> Pixel RGBA e -> Pixel RGBA e Source #

zipWithPx :: (e -> e -> e) -> Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel RGBA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel RGBA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel RGBA e -> e Source #

toListPx :: Pixel RGBA e -> [e] Source #

Functor (Pixel RGBA) Source # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGBA) Source # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Foldable (Pixel RGBA) Source # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Array arr RGBA Double => Readable [Image arr RGBA Double] [GIF] Source # 
Readable [Image VS RGBA Word8] [GIF] Source # 
Eq e => Eq (Pixel RGBA e) Source # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Floating e => Floating (Pixel RGBA e) Source # 
Fractional e => Fractional (Pixel RGBA e) Source # 
Num e => Num (Pixel RGBA e) Source # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Show e => Show (Pixel RGBA e) Source # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Storable e => Storable (Pixel RGBA e) Source # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Writable (Image VS RGBA Double) TIF Source # 
Writable (Image VS RGBA Double) TGA Source # 
Writable (Image VS RGBA Double) PNG Source # 
Writable (Image VS RGBA Double) JPG Source # 
Writable (Image VS RGBA Double) HDR Source # 
Writable (Image VS RGBA Double) GIF Source # 
Writable (Image VS RGBA Double) BMP Source # 
Writable (Image VS RGBA Word8) TIF Source # 
Writable (Image VS RGBA Word8) TGA Source # 
Writable (Image VS RGBA Word8) PNG Source # 
Writable (Image VS RGBA Word8) BMP Source # 
Writable (Image VS RGBA Word16) TIF Source # 
Writable (Image VS RGBA Word16) PNG Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) TIF Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) TGA Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) PNG Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) JPG Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) HDR Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) GIF Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) BMP Source # 
Array arr RGBA Double => Readable (Image arr RGBA Double) PPM Source # 
Readable (Image VS RGBA Word8) TIF Source # 
Readable (Image VS RGBA Word8) TGA Source # 
Readable (Image VS RGBA Word8) PNG Source # 
Readable (Image VS RGBA Word8) GIF Source # 
Readable (Image VS RGBA Word8) BMP Source # 
Readable (Image VS RGBA Word16) TIF Source # 
Readable (Image VS RGBA Word16) PNG Source # 
type Opaque RGBA Source # 
type Opaque RGBA = RGB
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
type Components RGBA e Source # 
type Components RGBA e = (e, e, e, e)

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class ColorSpace cs Double => ToRGB cs where Source #

Conversion to RGB color space.

Minimal complete definition

toPixelRGB

Methods

toPixelRGB :: Pixel cs Double -> Pixel RGB Double Source #

Convert to an RGB pixel.

toImageRGB :: (Array arr cs Double, Array arr RGB Double) => Image arr cs Double -> Image arr RGB Double Source #

Convert to an RGB image.

class (ToRGB (Opaque cs), AlphaSpace cs Double) => ToRGBA cs where Source #

Conversion to RGBA from another color space with Alpha channel.

Methods

toPixelRGBA :: Pixel cs Double -> Pixel RGBA Double Source #

Convert to an RGBA pixel.

toImageRGBA :: (Array arr cs Double, Array arr RGBA Double) => Image arr cs Double -> Image arr RGBA Double Source #

Convert to an RGBA image.

HSI

data HSI Source #

Hue, Saturation and Intensity color space.

Constructors

HueHSI

Hue

SatHSI

Saturation

IntHSI

Intensity

Instances

Enum HSI Source # 

Methods

succ :: HSI -> HSI #

pred :: HSI -> HSI #

toEnum :: Int -> HSI #

fromEnum :: HSI -> Int #

enumFrom :: HSI -> [HSI] #

enumFromThen :: HSI -> HSI -> [HSI] #

enumFromTo :: HSI -> HSI -> [HSI] #

enumFromThenTo :: HSI -> HSI -> HSI -> [HSI] #

Eq HSI Source # 

Methods

(==) :: HSI -> HSI -> Bool #

(/=) :: HSI -> HSI -> Bool #

Show HSI Source # 

Methods

showsPrec :: Int -> HSI -> ShowS #

show :: HSI -> String #

showList :: [HSI] -> ShowS #

ChannelColour HSI Source # 
(Elevator e, Typeable * e) => ColorSpace HSI e Source # 

Associated Types

type Components HSI e :: * Source #

Methods

toComponents :: Pixel HSI e -> Components HSI e Source #

fromComponents :: Components HSI e -> Pixel HSI e Source #

broadcastC :: e -> Pixel HSI e Source #

getPxC :: Pixel HSI e -> HSI -> e Source #

setPxC :: Pixel HSI e -> HSI -> e -> Pixel HSI e Source #

mapPxC :: (HSI -> e -> e) -> Pixel HSI e -> Pixel HSI e Source #

mapPx :: (e -> e) -> Pixel HSI e -> Pixel HSI e Source #

zipWithPx :: (e -> e -> e) -> Pixel HSI e -> Pixel HSI e -> Pixel HSI e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel HSI e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel HSI e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel HSI e -> e Source #

toListPx :: Pixel HSI e -> [e] Source #

Functor (Pixel HSI) Source # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel HSI) Source # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Foldable (Pixel HSI) Source # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Eq e => Eq (Pixel HSI e) Source # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Floating e => Floating (Pixel HSI e) Source # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Fractional e => Fractional (Pixel HSI e) Source # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Num e => Num (Pixel HSI e) Source # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Show e => Show (Pixel HSI e) Source # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Storable e => Storable (Pixel HSI e) Source # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
type Components HSI e Source # 
type Components HSI e = (e, e, e)

data HSIA Source #

Hue, Saturation and Intensity color space with Alpha channel.

Constructors

HueHSIA

Hue

SatHSIA

Saturation

IntHSIA

Intensity

AlphaHSIA

Alpha

Instances

Enum HSIA Source # 

Methods

succ :: HSIA -> HSIA #

pred :: HSIA -> HSIA #

toEnum :: Int -> HSIA #

fromEnum :: HSIA -> Int #

enumFrom :: HSIA -> [HSIA] #

enumFromThen :: HSIA -> HSIA -> [HSIA] #

enumFromTo :: HSIA -> HSIA -> [HSIA] #

enumFromThenTo :: HSIA -> HSIA -> HSIA -> [HSIA] #

Eq HSIA Source # 

Methods

(==) :: HSIA -> HSIA -> Bool #

(/=) :: HSIA -> HSIA -> Bool #

Show HSIA Source # 

Methods

showsPrec :: Int -> HSIA -> ShowS #

show :: HSIA -> String #

showList :: [HSIA] -> ShowS #

ChannelColour HSIA Source # 
(Elevator e, Typeable * e) => AlphaSpace HSIA e Source # 

Associated Types

type Opaque HSIA :: * Source #

(Elevator e, Typeable * e) => ColorSpace HSIA e Source # 

Associated Types

type Components HSIA e :: * Source #

Methods

toComponents :: Pixel HSIA e -> Components HSIA e Source #

fromComponents :: Components HSIA e -> Pixel HSIA e Source #

broadcastC :: e -> Pixel HSIA e Source #

getPxC :: Pixel HSIA e -> HSIA -> e Source #

setPxC :: Pixel HSIA e -> HSIA -> e -> Pixel HSIA e Source #

mapPxC :: (HSIA -> e -> e) -> Pixel HSIA e -> Pixel HSIA e Source #

mapPx :: (e -> e) -> Pixel HSIA e -> Pixel HSIA e Source #

zipWithPx :: (e -> e -> e) -> Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel HSIA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel HSIA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel HSIA e -> e Source #

toListPx :: Pixel HSIA e -> [e] Source #

Functor (Pixel HSIA) Source # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSIA) Source # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Foldable (Pixel HSIA) Source # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Eq e => Eq (Pixel HSIA e) Source # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Floating e => Floating (Pixel HSIA e) Source # 
Fractional e => Fractional (Pixel HSIA e) Source # 
Num e => Num (Pixel HSIA e) Source # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Show e => Show (Pixel HSIA e) Source # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Storable e => Storable (Pixel HSIA e) Source # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

type Opaque HSIA Source # 
type Opaque HSIA = HSI
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
type Components HSIA e Source # 
type Components HSIA e = (e, e, e, e)

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class ColorSpace cs Double => ToHSI cs where Source #

Conversion to HSI color space.

Minimal complete definition

toPixelHSI

Methods

toPixelHSI :: Pixel cs Double -> Pixel HSI Double Source #

Convert to an HSI pixel.

toImageHSI :: (Array arr cs Double, Array arr HSI Double) => Image arr cs Double -> Image arr HSI Double Source #

Convert to an HSI image.

class (ToHSI (Opaque cs), AlphaSpace cs Double) => ToHSIA cs where Source #

Conversion to HSIA from another color space with Alpha channel.

Methods

toPixelHSIA :: Pixel cs Double -> Pixel HSIA Double Source #

Convert to an HSIA pixel.

toImageHSIA :: (Array arr cs Double, Array arr HSIA Double) => Image arr cs Double -> Image arr HSIA Double Source #

Convert to an HSIA image.

CMYK

data CMYK Source #

Cyan, Magenta, Yellow and Black color space.

Constructors

CyanCMYK

Cyan

MagCMYK

Magenta

YelCMYK

Yellow

KeyCMYK

Key (Black)

Instances

Enum CMYK Source # 

Methods

succ :: CMYK -> CMYK #

pred :: CMYK -> CMYK #

toEnum :: Int -> CMYK #

fromEnum :: CMYK -> Int #

enumFrom :: CMYK -> [CMYK] #

enumFromThen :: CMYK -> CMYK -> [CMYK] #

enumFromTo :: CMYK -> CMYK -> [CMYK] #

enumFromThenTo :: CMYK -> CMYK -> CMYK -> [CMYK] #

Eq CMYK Source # 

Methods

(==) :: CMYK -> CMYK -> Bool #

(/=) :: CMYK -> CMYK -> Bool #

Show CMYK Source # 

Methods

showsPrec :: Int -> CMYK -> ShowS #

show :: CMYK -> String #

showList :: [CMYK] -> ShowS #

ChannelColour CMYK Source # 
(Elevator e, Typeable * e) => ColorSpace CMYK e Source # 

Associated Types

type Components CMYK e :: * Source #

Methods

toComponents :: Pixel CMYK e -> Components CMYK e Source #

fromComponents :: Components CMYK e -> Pixel CMYK e Source #

broadcastC :: e -> Pixel CMYK e Source #

getPxC :: Pixel CMYK e -> CMYK -> e Source #

setPxC :: Pixel CMYK e -> CMYK -> e -> Pixel CMYK e Source #

mapPxC :: (CMYK -> e -> e) -> Pixel CMYK e -> Pixel CMYK e Source #

mapPx :: (e -> e) -> Pixel CMYK e -> Pixel CMYK e Source #

zipWithPx :: (e -> e -> e) -> Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel CMYK e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel CMYK e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel CMYK e -> e Source #

toListPx :: Pixel CMYK e -> [e] Source #

Functor (Pixel CMYK) Source # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel CMYK) Source # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel CMYK) Source # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Eq e => Eq (Pixel CMYK e) Source # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Floating e => Floating (Pixel CMYK e) Source # 
Fractional e => Fractional (Pixel CMYK e) Source # 
Num e => Num (Pixel CMYK e) Source # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Show e => Show (Pixel CMYK e) Source # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Storable e => Storable (Pixel CMYK e) Source # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Writable (Image VS CMYK Double) TIF Source # 
Writable (Image VS CMYK Word8) TIF Source # 
Writable (Image VS CMYK Word8) JPG Source # 
Writable (Image VS CMYK Word16) TIF Source # 
Readable (Image VS CMYK Word8) TIF Source # 
Readable (Image VS CMYK Word8) JPG Source # 
Readable (Image VS CMYK Word16) TIF Source # 
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
type Components CMYK e Source # 
type Components CMYK e = (e, e, e, e)

data CMYKA Source #

Cyan, Magenta, Yellow and Black color space with Alpha channel.

Constructors

CyanCMYKA

Cyan

MagCMYKA

Magenta

YelCMYKA

Yellow

KeyCMYKA

Key (Black)

AlphaCMYKA

Alpha

Instances

Enum CMYKA Source # 
Eq CMYKA Source # 

Methods

(==) :: CMYKA -> CMYKA -> Bool #

(/=) :: CMYKA -> CMYKA -> Bool #

Show CMYKA Source # 

Methods

showsPrec :: Int -> CMYKA -> ShowS #

show :: CMYKA -> String #

showList :: [CMYKA] -> ShowS #

ChannelColour CMYKA Source # 
(Elevator e, Typeable * e) => AlphaSpace CMYKA e Source # 

Associated Types

type Opaque CMYKA :: * Source #

(Elevator e, Typeable * e) => ColorSpace CMYKA e Source # 

Associated Types

type Components CMYKA e :: * Source #

Methods

toComponents :: Pixel CMYKA e -> Components CMYKA e Source #

fromComponents :: Components CMYKA e -> Pixel CMYKA e Source #

broadcastC :: e -> Pixel CMYKA e Source #

getPxC :: Pixel CMYKA e -> CMYKA -> e Source #

setPxC :: Pixel CMYKA e -> CMYKA -> e -> Pixel CMYKA e Source #

mapPxC :: (CMYKA -> e -> e) -> Pixel CMYKA e -> Pixel CMYKA e Source #

mapPx :: (e -> e) -> Pixel CMYKA e -> Pixel CMYKA e Source #

zipWithPx :: (e -> e -> e) -> Pixel CMYKA e -> Pixel CMYKA e -> Pixel CMYKA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel CMYKA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel CMYKA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel CMYKA e -> e Source #

toListPx :: Pixel CMYKA e -> [e] Source #

Functor (Pixel CMYKA) Source # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYKA) Source # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Foldable (Pixel CMYKA) Source # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Eq e => Eq (Pixel CMYKA e) Source # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Floating e => Floating (Pixel CMYKA e) Source # 
Fractional e => Fractional (Pixel CMYKA e) Source # 
Num e => Num (Pixel CMYKA e) Source # 
Show e => Show (Pixel CMYKA e) Source # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Storable e => Storable (Pixel CMYKA e) Source # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

type Opaque CMYKA Source # 
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
type Components CMYKA e Source # 
type Components CMYKA e = (e, e, e, e, e)

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class ColorSpace cs Double => ToCMYK cs where Source #

Conversion to CMYK color space.

Minimal complete definition

toPixelCMYK

Methods

toPixelCMYK :: Pixel cs Double -> Pixel CMYK Double Source #

Convert to a CMYK pixel.

toImageCMYK :: (Array arr cs Double, Array arr CMYK Double) => Image arr cs Double -> Image arr CMYK Double Source #

Convert to a CMYK image.

class (ToCMYK (Opaque cs), AlphaSpace cs Double) => ToCMYKA cs where Source #

Conversion to CMYKA from another color space with Alpha channel.

Methods

toPixelCMYKA :: Pixel cs Double -> Pixel CMYKA Double Source #

Convert to a CMYKA pixel.

toImageCMYKA :: (Array arr cs Double, Array arr CMYKA Double) => Image arr cs Double -> Image arr CMYKA Double Source #

Convert to a CMYKA image.

YCbCr

data YCbCr Source #

Color space is used to encode RGB information and is used in JPEG compression.

Constructors

LumaYCbCr

Luma component (commonly denoted as Y')

CBlueYCbCr

Blue difference chroma component

CRedYCbCr

Red difference chroma component

Instances

Enum YCbCr Source # 
Eq YCbCr Source # 

Methods

(==) :: YCbCr -> YCbCr -> Bool #

(/=) :: YCbCr -> YCbCr -> Bool #

Show YCbCr Source # 

Methods

showsPrec :: Int -> YCbCr -> ShowS #

show :: YCbCr -> String #

showList :: [YCbCr] -> ShowS #

ChannelColour YCbCr Source # 
(Elevator e, Typeable * e) => ColorSpace YCbCr e Source # 

Associated Types

type Components YCbCr e :: * Source #

Methods

toComponents :: Pixel YCbCr e -> Components YCbCr e Source #

fromComponents :: Components YCbCr e -> Pixel YCbCr e Source #

broadcastC :: e -> Pixel YCbCr e Source #

getPxC :: Pixel YCbCr e -> YCbCr -> e Source #

setPxC :: Pixel YCbCr e -> YCbCr -> e -> Pixel YCbCr e Source #

mapPxC :: (YCbCr -> e -> e) -> Pixel YCbCr e -> Pixel YCbCr e Source #

mapPx :: (e -> e) -> Pixel YCbCr e -> Pixel YCbCr e Source #

zipWithPx :: (e -> e -> e) -> Pixel YCbCr e -> Pixel YCbCr e -> Pixel YCbCr e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YCbCr e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YCbCr e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YCbCr e -> e Source #

toListPx :: Pixel YCbCr e -> [e] Source #

Functor (Pixel YCbCr) Source # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel YCbCr) Source # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Foldable (Pixel YCbCr) Source # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Eq e => Eq (Pixel YCbCr e) Source # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Floating e => Floating (Pixel YCbCr e) Source # 
Fractional e => Fractional (Pixel YCbCr e) Source # 
Num e => Num (Pixel YCbCr e) Source # 
Show e => Show (Pixel YCbCr e) Source # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Storable e => Storable (Pixel YCbCr e) Source # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Writable (Image VS YCbCr Double) TIF Source # 
Writable (Image VS YCbCr Word8) TIF Source # 
Writable (Image VS YCbCr Word8) JPG Source # 
Readable (Image VS YCbCr Word8) JPG Source # 
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
type Components YCbCr e Source # 
type Components YCbCr e = (e, e, e)

data YCbCrA Source #

YCbCr color space with Alpha channel.

Constructors

LumaYCbCrA

Luma component (commonly denoted as Y')

CBlueYCbCrA

Blue difference chroma component

CRedYCbCrA

Red difference chroma component

AlphaYCbCrA

Alpha component.

Instances

Enum YCbCrA Source # 
Eq YCbCrA Source # 

Methods

(==) :: YCbCrA -> YCbCrA -> Bool #

(/=) :: YCbCrA -> YCbCrA -> Bool #

Show YCbCrA Source # 
ChannelColour YCbCrA Source # 
(Elevator e, Typeable * e) => AlphaSpace YCbCrA e Source # 

Associated Types

type Opaque YCbCrA :: * Source #

(Elevator e, Typeable * e) => ColorSpace YCbCrA e Source # 

Associated Types

type Components YCbCrA e :: * Source #

Methods

toComponents :: Pixel YCbCrA e -> Components YCbCrA e Source #

fromComponents :: Components YCbCrA e -> Pixel YCbCrA e Source #

broadcastC :: e -> Pixel YCbCrA e Source #

getPxC :: Pixel YCbCrA e -> YCbCrA -> e Source #

setPxC :: Pixel YCbCrA e -> YCbCrA -> e -> Pixel YCbCrA e Source #

mapPxC :: (YCbCrA -> e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

mapPx :: (e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

zipWithPx :: (e -> e -> e) -> Pixel YCbCrA e -> Pixel YCbCrA e -> Pixel YCbCrA e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel YCbCrA e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel YCbCrA e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel YCbCrA e -> e Source #

toListPx :: Pixel YCbCrA e -> [e] Source #

Functor (Pixel YCbCrA) Source # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCrA) Source # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Foldable (Pixel YCbCrA) Source # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Eq e => Eq (Pixel YCbCrA e) Source # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Floating e => Floating (Pixel YCbCrA e) Source # 
Fractional e => Fractional (Pixel YCbCrA e) Source # 
Num e => Num (Pixel YCbCrA e) Source # 
Show e => Show (Pixel YCbCrA e) Source # 
Storable e => Storable (Pixel YCbCrA e) Source # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

type Opaque YCbCrA Source # 
data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
type Components YCbCrA e Source # 
type Components YCbCrA e = (e, e, e, e)

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

class ColorSpace cs Double => ToYCbCr cs where Source #

Conversion to YCbCr color space.

Minimal complete definition

toPixelYCbCr

Methods

toPixelYCbCr :: Pixel cs Double -> Pixel YCbCr Double Source #

Convert to an YCbCr pixel.

toImageYCbCr :: (Array arr cs Double, Array arr YCbCr Double) => Image arr cs Double -> Image arr YCbCr Double Source #

Convert to an YCbCr image.

class (ToYCbCr (Opaque cs), AlphaSpace cs Double) => ToYCbCrA cs where Source #

Conversion to YCbCrA from another color space with Alpha channel.

Methods

toPixelYCbCrA :: Pixel cs Double -> Pixel YCbCrA Double Source #

Convert to an YCbCrA pixel.

toImageYCbCrA :: (Array arr cs Double, Array arr YCbCrA Double) => Image arr cs Double -> Image arr YCbCrA Double Source #

Convert to an YCbCrA image.

Gray

data Gray Source #

This is a single channel colorspace, that is designed to separate Gray level values from other types of colorspace, hence it is not convertible to or from, but rather is here to allow operation on arbirtary single channel images. If you are looking for a true grayscale colorspace Y should be used instead.

Constructors

Gray 

Instances

Enum Gray Source # 

Methods

succ :: Gray -> Gray #

pred :: Gray -> Gray #

toEnum :: Int -> Gray #

fromEnum :: Gray -> Int #

enumFrom :: Gray -> [Gray] #

enumFromThen :: Gray -> Gray -> [Gray] #

enumFromTo :: Gray -> Gray -> [Gray] #

enumFromThenTo :: Gray -> Gray -> Gray -> [Gray] #

Eq Gray Source # 

Methods

(==) :: Gray -> Gray -> Bool #

(/=) :: Gray -> Gray -> Bool #

Show Gray Source # 

Methods

showsPrec :: Int -> Gray -> ShowS #

show :: Gray -> String #

showList :: [Gray] -> ShowS #

ChannelColour Gray Source # 
(Elevator e, Typeable * e) => ColorSpace Gray e Source # 

Associated Types

type Components Gray e :: * Source #

Methods

toComponents :: Pixel Gray e -> Components Gray e Source #

fromComponents :: Components Gray e -> Pixel Gray e Source #

broadcastC :: e -> Pixel Gray e Source #

getPxC :: Pixel Gray e -> Gray -> e Source #

setPxC :: Pixel Gray e -> Gray -> e -> Pixel Gray e Source #

mapPxC :: (Gray -> e -> e) -> Pixel Gray e -> Pixel Gray e Source #

mapPx :: (e -> e) -> Pixel Gray e -> Pixel Gray e Source #

zipWithPx :: (e -> e -> e) -> Pixel Gray e -> Pixel Gray e -> Pixel Gray e Source #

foldrPx :: (e -> b -> b) -> b -> Pixel Gray e -> b Source #

foldlPx :: (b -> e -> b) -> b -> Pixel Gray e -> b Source #

foldl1Px :: (e -> e -> e) -> Pixel Gray e -> e Source #

toListPx :: Pixel Gray e -> [e] Source #

Monad (Pixel Gray) Source # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel Gray) Source # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel Gray) Source # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Foldable (Pixel Gray) Source # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Eq e => Eq (Pixel Gray e) Source # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Floating e => Floating (Pixel Gray e) Source # 
Fractional e => Fractional (Pixel Gray e) Source # 
Num e => Num (Pixel Gray e) Source # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Ord e => Ord (Pixel Gray e) Source # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Show e => Show (Pixel Gray e) Source # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Storable e => Storable (Pixel Gray e) Source # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
type Components Gray e Source # 
type Components Gray e = e

data family Pixel cs e :: * Source #

A Pixel family with a color space and a precision of elements.

Instances

Array arr Binary Bit => Thresholding Pixel (Image arr) arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Pixel cs e -> Image arr cs e -> Image arr Binary Bit Source #

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

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

Monad (Pixel Y) # 

Methods

(>>=) :: Pixel Y a -> (a -> Pixel Y b) -> Pixel Y b #

(>>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

return :: a -> Pixel Y a #

fail :: String -> Pixel Y a #

Monad (Pixel Gray) # 

Methods

(>>=) :: Pixel Gray a -> (a -> Pixel Gray b) -> Pixel Gray b #

(>>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

return :: a -> Pixel Gray a #

fail :: String -> Pixel Gray a #

Functor (Pixel YCbCrA) # 

Methods

fmap :: (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(<$) :: a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Functor (Pixel YCbCr) # 

Methods

fmap :: (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(<$) :: a -> Pixel YCbCr b -> Pixel YCbCr a #

Functor (Pixel RGBA) # 

Methods

fmap :: (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(<$) :: a -> Pixel RGBA b -> Pixel RGBA a #

Functor (Pixel RGB) # 

Methods

fmap :: (a -> b) -> Pixel RGB a -> Pixel RGB b #

(<$) :: a -> Pixel RGB b -> Pixel RGB a #

Functor (Pixel YA) # 

Methods

fmap :: (a -> b) -> Pixel YA a -> Pixel YA b #

(<$) :: a -> Pixel YA b -> Pixel YA a #

Functor (Pixel Y) # 

Methods

fmap :: (a -> b) -> Pixel Y a -> Pixel Y b #

(<$) :: a -> Pixel Y b -> Pixel Y a #

Functor (Pixel HSIA) # 

Methods

fmap :: (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(<$) :: a -> Pixel HSIA b -> Pixel HSIA a #

Functor (Pixel HSI) # 

Methods

fmap :: (a -> b) -> Pixel HSI a -> Pixel HSI b #

(<$) :: a -> Pixel HSI b -> Pixel HSI a #

Functor (Pixel Gray) # 

Methods

fmap :: (a -> b) -> Pixel Gray a -> Pixel Gray b #

(<$) :: a -> Pixel Gray b -> Pixel Gray a #

Functor (Pixel CMYKA) # 

Methods

fmap :: (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(<$) :: a -> Pixel CMYKA b -> Pixel CMYKA a #

Functor (Pixel CMYK) # 

Methods

fmap :: (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(<$) :: a -> Pixel CMYK b -> Pixel CMYK a #

Applicative (Pixel YCbCrA) # 

Methods

pure :: a -> Pixel YCbCrA a #

(<*>) :: Pixel YCbCrA (a -> b) -> Pixel YCbCrA a -> Pixel YCbCrA b #

(*>) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA b #

(<*) :: Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA a #

Applicative (Pixel YCbCr) # 

Methods

pure :: a -> Pixel YCbCr a #

(<*>) :: Pixel YCbCr (a -> b) -> Pixel YCbCr a -> Pixel YCbCr b #

(*>) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr b #

(<*) :: Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr a #

Applicative (Pixel RGBA) # 

Methods

pure :: a -> Pixel RGBA a #

(<*>) :: Pixel RGBA (a -> b) -> Pixel RGBA a -> Pixel RGBA b #

(*>) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA b #

(<*) :: Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA a #

Applicative (Pixel RGB) # 

Methods

pure :: a -> Pixel RGB a #

(<*>) :: Pixel RGB (a -> b) -> Pixel RGB a -> Pixel RGB b #

(*>) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB b #

(<*) :: Pixel RGB a -> Pixel RGB b -> Pixel RGB a #

Applicative (Pixel YA) # 

Methods

pure :: a -> Pixel YA a #

(<*>) :: Pixel YA (a -> b) -> Pixel YA a -> Pixel YA b #

(*>) :: Pixel YA a -> Pixel YA b -> Pixel YA b #

(<*) :: Pixel YA a -> Pixel YA b -> Pixel YA a #

Applicative (Pixel Y) # 

Methods

pure :: a -> Pixel Y a #

(<*>) :: Pixel Y (a -> b) -> Pixel Y a -> Pixel Y b #

(*>) :: Pixel Y a -> Pixel Y b -> Pixel Y b #

(<*) :: Pixel Y a -> Pixel Y b -> Pixel Y a #

Applicative (Pixel HSIA) # 

Methods

pure :: a -> Pixel HSIA a #

(<*>) :: Pixel HSIA (a -> b) -> Pixel HSIA a -> Pixel HSIA b #

(*>) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA b #

(<*) :: Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA a #

Applicative (Pixel HSI) # 

Methods

pure :: a -> Pixel HSI a #

(<*>) :: Pixel HSI (a -> b) -> Pixel HSI a -> Pixel HSI b #

(*>) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI b #

(<*) :: Pixel HSI a -> Pixel HSI b -> Pixel HSI a #

Applicative (Pixel Gray) # 

Methods

pure :: a -> Pixel Gray a #

(<*>) :: Pixel Gray (a -> b) -> Pixel Gray a -> Pixel Gray b #

(*>) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray b #

(<*) :: Pixel Gray a -> Pixel Gray b -> Pixel Gray a #

Applicative (Pixel CMYKA) # 

Methods

pure :: a -> Pixel CMYKA a #

(<*>) :: Pixel CMYKA (a -> b) -> Pixel CMYKA a -> Pixel CMYKA b #

(*>) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA b #

(<*) :: Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA a #

Applicative (Pixel CMYK) # 

Methods

pure :: a -> Pixel CMYK a #

(<*>) :: Pixel CMYK (a -> b) -> Pixel CMYK a -> Pixel CMYK b #

(*>) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK b #

(<*) :: Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK a #

Foldable (Pixel YCbCrA) # 

Methods

fold :: Monoid m => Pixel YCbCrA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCrA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCrA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCrA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCrA a -> a #

toList :: Pixel YCbCrA a -> [a] #

null :: Pixel YCbCrA a -> Bool #

length :: Pixel YCbCrA a -> Int #

elem :: Eq a => a -> Pixel YCbCrA a -> Bool #

maximum :: Ord a => Pixel YCbCrA a -> a #

minimum :: Ord a => Pixel YCbCrA a -> a #

sum :: Num a => Pixel YCbCrA a -> a #

product :: Num a => Pixel YCbCrA a -> a #

Foldable (Pixel YCbCr) # 

Methods

fold :: Monoid m => Pixel YCbCr m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YCbCr a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YCbCr a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YCbCr a -> b #

foldr1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

foldl1 :: (a -> a -> a) -> Pixel YCbCr a -> a #

toList :: Pixel YCbCr a -> [a] #

null :: Pixel YCbCr a -> Bool #

length :: Pixel YCbCr a -> Int #

elem :: Eq a => a -> Pixel YCbCr a -> Bool #

maximum :: Ord a => Pixel YCbCr a -> a #

minimum :: Ord a => Pixel YCbCr a -> a #

sum :: Num a => Pixel YCbCr a -> a #

product :: Num a => Pixel YCbCr a -> a #

Foldable (Pixel RGBA) # 

Methods

fold :: Monoid m => Pixel RGBA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGBA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGBA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGBA a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGBA a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGBA a -> a #

toList :: Pixel RGBA a -> [a] #

null :: Pixel RGBA a -> Bool #

length :: Pixel RGBA a -> Int #

elem :: Eq a => a -> Pixel RGBA a -> Bool #

maximum :: Ord a => Pixel RGBA a -> a #

minimum :: Ord a => Pixel RGBA a -> a #

sum :: Num a => Pixel RGBA a -> a #

product :: Num a => Pixel RGBA a -> a #

Foldable (Pixel RGB) # 

Methods

fold :: Monoid m => Pixel RGB m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel RGB a -> m #

foldr :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel RGB a -> b #

foldl :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel RGB a -> b #

foldr1 :: (a -> a -> a) -> Pixel RGB a -> a #

foldl1 :: (a -> a -> a) -> Pixel RGB a -> a #

toList :: Pixel RGB a -> [a] #

null :: Pixel RGB a -> Bool #

length :: Pixel RGB a -> Int #

elem :: Eq a => a -> Pixel RGB a -> Bool #

maximum :: Ord a => Pixel RGB a -> a #

minimum :: Ord a => Pixel RGB a -> a #

sum :: Num a => Pixel RGB a -> a #

product :: Num a => Pixel RGB a -> a #

Foldable (Pixel YA) # 

Methods

fold :: Monoid m => Pixel YA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel YA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel YA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel YA a -> b #

foldr1 :: (a -> a -> a) -> Pixel YA a -> a #

foldl1 :: (a -> a -> a) -> Pixel YA a -> a #

toList :: Pixel YA a -> [a] #

null :: Pixel YA a -> Bool #

length :: Pixel YA a -> Int #

elem :: Eq a => a -> Pixel YA a -> Bool #

maximum :: Ord a => Pixel YA a -> a #

minimum :: Ord a => Pixel YA a -> a #

sum :: Num a => Pixel YA a -> a #

product :: Num a => Pixel YA a -> a #

Foldable (Pixel Y) # 

Methods

fold :: Monoid m => Pixel Y m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Y a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Y a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Y a -> b #

foldr1 :: (a -> a -> a) -> Pixel Y a -> a #

foldl1 :: (a -> a -> a) -> Pixel Y a -> a #

toList :: Pixel Y a -> [a] #

null :: Pixel Y a -> Bool #

length :: Pixel Y a -> Int #

elem :: Eq a => a -> Pixel Y a -> Bool #

maximum :: Ord a => Pixel Y a -> a #

minimum :: Ord a => Pixel Y a -> a #

sum :: Num a => Pixel Y a -> a #

product :: Num a => Pixel Y a -> a #

Foldable (Pixel HSIA) # 

Methods

fold :: Monoid m => Pixel HSIA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSIA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSIA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSIA a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSIA a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSIA a -> a #

toList :: Pixel HSIA a -> [a] #

null :: Pixel HSIA a -> Bool #

length :: Pixel HSIA a -> Int #

elem :: Eq a => a -> Pixel HSIA a -> Bool #

maximum :: Ord a => Pixel HSIA a -> a #

minimum :: Ord a => Pixel HSIA a -> a #

sum :: Num a => Pixel HSIA a -> a #

product :: Num a => Pixel HSIA a -> a #

Foldable (Pixel HSI) # 

Methods

fold :: Monoid m => Pixel HSI m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel HSI a -> m #

foldr :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel HSI a -> b #

foldl :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel HSI a -> b #

foldr1 :: (a -> a -> a) -> Pixel HSI a -> a #

foldl1 :: (a -> a -> a) -> Pixel HSI a -> a #

toList :: Pixel HSI a -> [a] #

null :: Pixel HSI a -> Bool #

length :: Pixel HSI a -> Int #

elem :: Eq a => a -> Pixel HSI a -> Bool #

maximum :: Ord a => Pixel HSI a -> a #

minimum :: Ord a => Pixel HSI a -> a #

sum :: Num a => Pixel HSI a -> a #

product :: Num a => Pixel HSI a -> a #

Foldable (Pixel Gray) # 

Methods

fold :: Monoid m => Pixel Gray m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel Gray a -> m #

foldr :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel Gray a -> b #

foldl :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel Gray a -> b #

foldr1 :: (a -> a -> a) -> Pixel Gray a -> a #

foldl1 :: (a -> a -> a) -> Pixel Gray a -> a #

toList :: Pixel Gray a -> [a] #

null :: Pixel Gray a -> Bool #

length :: Pixel Gray a -> Int #

elem :: Eq a => a -> Pixel Gray a -> Bool #

maximum :: Ord a => Pixel Gray a -> a #

minimum :: Ord a => Pixel Gray a -> a #

sum :: Num a => Pixel Gray a -> a #

product :: Num a => Pixel Gray a -> a #

Foldable (Pixel CMYKA) # 

Methods

fold :: Monoid m => Pixel CMYKA m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYKA a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYKA a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYKA a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYKA a -> a #

toList :: Pixel CMYKA a -> [a] #

null :: Pixel CMYKA a -> Bool #

length :: Pixel CMYKA a -> Int #

elem :: Eq a => a -> Pixel CMYKA a -> Bool #

maximum :: Ord a => Pixel CMYKA a -> a #

minimum :: Ord a => Pixel CMYKA a -> a #

sum :: Num a => Pixel CMYKA a -> a #

product :: Num a => Pixel CMYKA a -> a #

Foldable (Pixel CMYK) # 

Methods

fold :: Monoid m => Pixel CMYK m -> m #

foldMap :: Monoid m => (a -> m) -> Pixel CMYK a -> m #

foldr :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldr' :: (a -> b -> b) -> b -> Pixel CMYK a -> b #

foldl :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldl' :: (b -> a -> b) -> b -> Pixel CMYK a -> b #

foldr1 :: (a -> a -> a) -> Pixel CMYK a -> a #

foldl1 :: (a -> a -> a) -> Pixel CMYK a -> a #

toList :: Pixel CMYK a -> [a] #

null :: Pixel CMYK a -> Bool #

length :: Pixel CMYK a -> Int #

elem :: Eq a => a -> Pixel CMYK a -> Bool #

maximum :: Ord a => Pixel CMYK a -> a #

minimum :: Ord a => Pixel CMYK a -> a #

sum :: Num a => Pixel CMYK a -> a #

product :: Num a => Pixel CMYK a -> a #

Array arr Binary Bit => Thresholding (Image arr) Pixel arr Source # 

Methods

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

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

(.<.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

(.<=.) :: (Ord (Pixel cs e), Array arr cs e) => Image arr cs e -> Pixel cs e -> Image arr Binary Bit Source #

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

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

(Applicative (Pixel cs), Bounded e) => Bounded (Pixel cs e) Source # 

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) # 

Methods

(==) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

(/=) :: Pixel YCbCrA e -> Pixel YCbCrA e -> Bool #

Eq e => Eq (Pixel YCbCr e) # 

Methods

(==) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

(/=) :: Pixel YCbCr e -> Pixel YCbCr e -> Bool #

Eq e => Eq (Pixel RGBA e) # 

Methods

(==) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

(/=) :: Pixel RGBA e -> Pixel RGBA e -> Bool #

Eq e => Eq (Pixel RGB e) # 

Methods

(==) :: Pixel RGB e -> Pixel RGB e -> Bool #

(/=) :: Pixel RGB e -> Pixel RGB e -> Bool #

Eq e => Eq (Pixel YA e) # 

Methods

(==) :: Pixel YA e -> Pixel YA e -> Bool #

(/=) :: Pixel YA e -> Pixel YA e -> Bool #

Eq e => Eq (Pixel Y e) # 

Methods

(==) :: Pixel Y e -> Pixel Y e -> Bool #

(/=) :: Pixel Y e -> Pixel Y e -> Bool #

Eq e => Eq (Pixel HSIA e) # 

Methods

(==) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

(/=) :: Pixel HSIA e -> Pixel HSIA e -> Bool #

Eq e => Eq (Pixel HSI e) # 

Methods

(==) :: Pixel HSI e -> Pixel HSI e -> Bool #

(/=) :: Pixel HSI e -> Pixel HSI e -> Bool #

Eq e => Eq (Pixel Gray e) # 

Methods

(==) :: Pixel Gray e -> Pixel Gray e -> Bool #

(/=) :: Pixel Gray e -> Pixel Gray e -> Bool #

Eq e => Eq (Pixel CMYKA e) # 

Methods

(==) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

(/=) :: Pixel CMYKA e -> Pixel CMYKA e -> Bool #

Eq e => Eq (Pixel CMYK e) # 

Methods

(==) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

(/=) :: Pixel CMYK e -> Pixel CMYK e -> Bool #

Eq e => Eq (Pixel Binary e) # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Floating e => Floating (Pixel YCbCrA e) # 
Floating e => Floating (Pixel YCbCr e) # 
Floating e => Floating (Pixel RGBA e) # 
Floating e => Floating (Pixel RGB e) # 

Methods

pi :: Pixel RGB e #

exp :: Pixel RGB e -> Pixel RGB e #

log :: Pixel RGB e -> Pixel RGB e #

sqrt :: Pixel RGB e -> Pixel RGB e #

(**) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

logBase :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

sin :: Pixel RGB e -> Pixel RGB e #

cos :: Pixel RGB e -> Pixel RGB e #

tan :: Pixel RGB e -> Pixel RGB e #

asin :: Pixel RGB e -> Pixel RGB e #

acos :: Pixel RGB e -> Pixel RGB e #

atan :: Pixel RGB e -> Pixel RGB e #

sinh :: Pixel RGB e -> Pixel RGB e #

cosh :: Pixel RGB e -> Pixel RGB e #

tanh :: Pixel RGB e -> Pixel RGB e #

asinh :: Pixel RGB e -> Pixel RGB e #

acosh :: Pixel RGB e -> Pixel RGB e #

atanh :: Pixel RGB e -> Pixel RGB e #

log1p :: Pixel RGB e -> Pixel RGB e #

expm1 :: Pixel RGB e -> Pixel RGB e #

log1pexp :: Pixel RGB e -> Pixel RGB e #

log1mexp :: Pixel RGB e -> Pixel RGB e #

Floating e => Floating (Pixel YA e) # 

Methods

pi :: Pixel YA e #

exp :: Pixel YA e -> Pixel YA e #

log :: Pixel YA e -> Pixel YA e #

sqrt :: Pixel YA e -> Pixel YA e #

(**) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

logBase :: Pixel YA e -> Pixel YA e -> Pixel YA e #

sin :: Pixel YA e -> Pixel YA e #

cos :: Pixel YA e -> Pixel YA e #

tan :: Pixel YA e -> Pixel YA e #

asin :: Pixel YA e -> Pixel YA e #

acos :: Pixel YA e -> Pixel YA e #

atan :: Pixel YA e -> Pixel YA e #

sinh :: Pixel YA e -> Pixel YA e #

cosh :: Pixel YA e -> Pixel YA e #

tanh :: Pixel YA e -> Pixel YA e #

asinh :: Pixel YA e -> Pixel YA e #

acosh :: Pixel YA e -> Pixel YA e #

atanh :: Pixel YA e -> Pixel YA e #

log1p :: Pixel YA e -> Pixel YA e #

expm1 :: Pixel YA e -> Pixel YA e #

log1pexp :: Pixel YA e -> Pixel YA e #

log1mexp :: Pixel YA e -> Pixel YA e #

Floating e => Floating (Pixel Y e) # 

Methods

pi :: Pixel Y e #

exp :: Pixel Y e -> Pixel Y e #

log :: Pixel Y e -> Pixel Y e #

sqrt :: Pixel Y e -> Pixel Y e #

(**) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

logBase :: Pixel Y e -> Pixel Y e -> Pixel Y e #

sin :: Pixel Y e -> Pixel Y e #

cos :: Pixel Y e -> Pixel Y e #

tan :: Pixel Y e -> Pixel Y e #

asin :: Pixel Y e -> Pixel Y e #

acos :: Pixel Y e -> Pixel Y e #

atan :: Pixel Y e -> Pixel Y e #

sinh :: Pixel Y e -> Pixel Y e #

cosh :: Pixel Y e -> Pixel Y e #

tanh :: Pixel Y e -> Pixel Y e #

asinh :: Pixel Y e -> Pixel Y e #

acosh :: Pixel Y e -> Pixel Y e #

atanh :: Pixel Y e -> Pixel Y e #

log1p :: Pixel Y e -> Pixel Y e #

expm1 :: Pixel Y e -> Pixel Y e #

log1pexp :: Pixel Y e -> Pixel Y e #

log1mexp :: Pixel Y e -> Pixel Y e #

Floating e => Floating (Pixel HSIA e) # 
Floating e => Floating (Pixel HSI e) # 

Methods

pi :: Pixel HSI e #

exp :: Pixel HSI e -> Pixel HSI e #

log :: Pixel HSI e -> Pixel HSI e #

sqrt :: Pixel HSI e -> Pixel HSI e #

(**) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

logBase :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

sin :: Pixel HSI e -> Pixel HSI e #

cos :: Pixel HSI e -> Pixel HSI e #

tan :: Pixel HSI e -> Pixel HSI e #

asin :: Pixel HSI e -> Pixel HSI e #

acos :: Pixel HSI e -> Pixel HSI e #

atan :: Pixel HSI e -> Pixel HSI e #

sinh :: Pixel HSI e -> Pixel HSI e #

cosh :: Pixel HSI e -> Pixel HSI e #

tanh :: Pixel HSI e -> Pixel HSI e #

asinh :: Pixel HSI e -> Pixel HSI e #

acosh :: Pixel HSI e -> Pixel HSI e #

atanh :: Pixel HSI e -> Pixel HSI e #

log1p :: Pixel HSI e -> Pixel HSI e #

expm1 :: Pixel HSI e -> Pixel HSI e #

log1pexp :: Pixel HSI e -> Pixel HSI e #

log1mexp :: Pixel HSI e -> Pixel HSI e #

Floating e => Floating (Pixel Gray e) # 
Floating e => Floating (Pixel CMYKA e) # 
Floating e => Floating (Pixel CMYK e) # 
Fractional e => Fractional (Pixel YCbCrA e) # 
Fractional e => Fractional (Pixel YCbCr e) # 
Fractional e => Fractional (Pixel RGBA e) # 
Fractional e => Fractional (Pixel RGB e) # 

Methods

(/) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

recip :: Pixel RGB e -> Pixel RGB e #

fromRational :: Rational -> Pixel RGB e #

Fractional e => Fractional (Pixel YA e) # 

Methods

(/) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

recip :: Pixel YA e -> Pixel YA e #

fromRational :: Rational -> Pixel YA e #

Fractional e => Fractional (Pixel Y e) # 

Methods

(/) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

recip :: Pixel Y e -> Pixel Y e #

fromRational :: Rational -> Pixel Y e #

Fractional e => Fractional (Pixel HSIA e) # 
Fractional e => Fractional (Pixel HSI e) # 

Methods

(/) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

recip :: Pixel HSI e -> Pixel HSI e #

fromRational :: Rational -> Pixel HSI e #

Fractional e => Fractional (Pixel Gray e) # 
Fractional e => Fractional (Pixel CMYKA e) # 
Fractional e => Fractional (Pixel CMYK e) # 
Num e => Num (Pixel YCbCrA e) # 
Num e => Num (Pixel YCbCr e) # 
Num e => Num (Pixel RGBA e) # 

Methods

(+) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(-) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

(*) :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

negate :: Pixel RGBA e -> Pixel RGBA e #

abs :: Pixel RGBA e -> Pixel RGBA e #

signum :: Pixel RGBA e -> Pixel RGBA e #

fromInteger :: Integer -> Pixel RGBA e #

Num e => Num (Pixel RGB e) # 

Methods

(+) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(-) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

(*) :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

negate :: Pixel RGB e -> Pixel RGB e #

abs :: Pixel RGB e -> Pixel RGB e #

signum :: Pixel RGB e -> Pixel RGB e #

fromInteger :: Integer -> Pixel RGB e #

Num e => Num (Pixel YA e) # 

Methods

(+) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(-) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

(*) :: Pixel YA e -> Pixel YA e -> Pixel YA e #

negate :: Pixel YA e -> Pixel YA e #

abs :: Pixel YA e -> Pixel YA e #

signum :: Pixel YA e -> Pixel YA e #

fromInteger :: Integer -> Pixel YA e #

Num e => Num (Pixel Y e) # 

Methods

(+) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(-) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

(*) :: Pixel Y e -> Pixel Y e -> Pixel Y e #

negate :: Pixel Y e -> Pixel Y e #

abs :: Pixel Y e -> Pixel Y e #

signum :: Pixel Y e -> Pixel Y e #

fromInteger :: Integer -> Pixel Y e #

Num e => Num (Pixel HSIA e) # 

Methods

(+) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(-) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

(*) :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

negate :: Pixel HSIA e -> Pixel HSIA e #

abs :: Pixel HSIA e -> Pixel HSIA e #

signum :: Pixel HSIA e -> Pixel HSIA e #

fromInteger :: Integer -> Pixel HSIA e #

Num e => Num (Pixel HSI e) # 

Methods

(+) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(-) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

(*) :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

negate :: Pixel HSI e -> Pixel HSI e #

abs :: Pixel HSI e -> Pixel HSI e #

signum :: Pixel HSI e -> Pixel HSI e #

fromInteger :: Integer -> Pixel HSI e #

Num e => Num (Pixel Gray e) # 

Methods

(+) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(-) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

(*) :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

negate :: Pixel Gray e -> Pixel Gray e #

abs :: Pixel Gray e -> Pixel Gray e #

signum :: Pixel Gray e -> Pixel Gray e #

fromInteger :: Integer -> Pixel Gray e #

Num e => Num (Pixel CMYKA e) # 
Num e => Num (Pixel CMYK e) # 

Methods

(+) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(-) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

(*) :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

negate :: Pixel CMYK e -> Pixel CMYK e #

abs :: Pixel CMYK e -> Pixel CMYK e #

signum :: Pixel CMYK e -> Pixel CMYK e #

fromInteger :: Integer -> Pixel CMYK e #

Num (Pixel Binary Bit) # 
Ord e => Ord (Pixel Y e) # 

Methods

compare :: Pixel Y e -> Pixel Y e -> Ordering #

(<) :: Pixel Y e -> Pixel Y e -> Bool #

(<=) :: Pixel Y e -> Pixel Y e -> Bool #

(>) :: Pixel Y e -> Pixel Y e -> Bool #

(>=) :: Pixel Y e -> Pixel Y e -> Bool #

max :: Pixel Y e -> Pixel Y e -> Pixel Y e #

min :: Pixel Y e -> Pixel Y e -> Pixel Y e #

Ord e => Ord (Pixel Gray e) # 

Methods

compare :: Pixel Gray e -> Pixel Gray e -> Ordering #

(<) :: Pixel Gray e -> Pixel Gray e -> Bool #

(<=) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>) :: Pixel Gray e -> Pixel Gray e -> Bool #

(>=) :: Pixel Gray e -> Pixel Gray e -> Bool #

max :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

min :: Pixel Gray e -> Pixel Gray e -> Pixel Gray e #

Ord e => Ord (Pixel Binary e) # 
Show e => Show (Pixel YCbCrA e) # 
Show e => Show (Pixel YCbCr e) # 

Methods

showsPrec :: Int -> Pixel YCbCr e -> ShowS #

show :: Pixel YCbCr e -> String #

showList :: [Pixel YCbCr e] -> ShowS #

Show e => Show (Pixel RGBA e) # 

Methods

showsPrec :: Int -> Pixel RGBA e -> ShowS #

show :: Pixel RGBA e -> String #

showList :: [Pixel RGBA e] -> ShowS #

Show e => Show (Pixel RGB e) # 

Methods

showsPrec :: Int -> Pixel RGB e -> ShowS #

show :: Pixel RGB e -> String #

showList :: [Pixel RGB e] -> ShowS #

Show e => Show (Pixel Y e) # 

Methods

showsPrec :: Int -> Pixel Y e -> ShowS #

show :: Pixel Y e -> String #

showList :: [Pixel Y e] -> ShowS #

Show e => Show (Pixel HSIA e) # 

Methods

showsPrec :: Int -> Pixel HSIA e -> ShowS #

show :: Pixel HSIA e -> String #

showList :: [Pixel HSIA e] -> ShowS #

Show e => Show (Pixel HSI e) # 

Methods

showsPrec :: Int -> Pixel HSI e -> ShowS #

show :: Pixel HSI e -> String #

showList :: [Pixel HSI e] -> ShowS #

Show e => Show (Pixel Gray e) # 

Methods

showsPrec :: Int -> Pixel Gray e -> ShowS #

show :: Pixel Gray e -> String #

showList :: [Pixel Gray e] -> ShowS #

Show e => Show (Pixel CMYKA e) # 

Methods

showsPrec :: Int -> Pixel CMYKA e -> ShowS #

show :: Pixel CMYKA e -> String #

showList :: [Pixel CMYKA e] -> ShowS #

Show e => Show (Pixel CMYK e) # 

Methods

showsPrec :: Int -> Pixel CMYK e -> ShowS #

show :: Pixel CMYK e -> String #

showList :: [Pixel CMYK e] -> ShowS #

Show (Pixel Binary Bit) # 
Storable e => Storable (Pixel YCbCrA e) # 

Methods

sizeOf :: Pixel YCbCrA e -> Int #

alignment :: Pixel YCbCrA e -> Int #

peekElemOff :: Ptr (Pixel YCbCrA e) -> Int -> IO (Pixel YCbCrA e) #

pokeElemOff :: Ptr (Pixel YCbCrA e) -> Int -> Pixel YCbCrA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCrA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCrA e -> IO () #

peek :: Ptr (Pixel YCbCrA e) -> IO (Pixel YCbCrA e) #

poke :: Ptr (Pixel YCbCrA e) -> Pixel YCbCrA e -> IO () #

Storable e => Storable (Pixel YCbCr e) # 

Methods

sizeOf :: Pixel YCbCr e -> Int #

alignment :: Pixel YCbCr e -> Int #

peekElemOff :: Ptr (Pixel YCbCr e) -> Int -> IO (Pixel YCbCr e) #

pokeElemOff :: Ptr (Pixel YCbCr e) -> Int -> Pixel YCbCr e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YCbCr e) #

pokeByteOff :: Ptr b -> Int -> Pixel YCbCr e -> IO () #

peek :: Ptr (Pixel YCbCr e) -> IO (Pixel YCbCr e) #

poke :: Ptr (Pixel YCbCr e) -> Pixel YCbCr e -> IO () #

Storable e => Storable (Pixel RGBA e) # 

Methods

sizeOf :: Pixel RGBA e -> Int #

alignment :: Pixel RGBA e -> Int #

peekElemOff :: Ptr (Pixel RGBA e) -> Int -> IO (Pixel RGBA e) #

pokeElemOff :: Ptr (Pixel RGBA e) -> Int -> Pixel RGBA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGBA e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGBA e -> IO () #

peek :: Ptr (Pixel RGBA e) -> IO (Pixel RGBA e) #

poke :: Ptr (Pixel RGBA e) -> Pixel RGBA e -> IO () #

Storable e => Storable (Pixel RGB e) # 

Methods

sizeOf :: Pixel RGB e -> Int #

alignment :: Pixel RGB e -> Int #

peekElemOff :: Ptr (Pixel RGB e) -> Int -> IO (Pixel RGB e) #

pokeElemOff :: Ptr (Pixel RGB e) -> Int -> Pixel RGB e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel RGB e) #

pokeByteOff :: Ptr b -> Int -> Pixel RGB e -> IO () #

peek :: Ptr (Pixel RGB e) -> IO (Pixel RGB e) #

poke :: Ptr (Pixel RGB e) -> Pixel RGB e -> IO () #

Storable e => Storable (Pixel YA e) # 

Methods

sizeOf :: Pixel YA e -> Int #

alignment :: Pixel YA e -> Int #

peekElemOff :: Ptr (Pixel YA e) -> Int -> IO (Pixel YA e) #

pokeElemOff :: Ptr (Pixel YA e) -> Int -> Pixel YA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel YA e) #

pokeByteOff :: Ptr b -> Int -> Pixel YA e -> IO () #

peek :: Ptr (Pixel YA e) -> IO (Pixel YA e) #

poke :: Ptr (Pixel YA e) -> Pixel YA e -> IO () #

Storable e => Storable (Pixel Y e) # 

Methods

sizeOf :: Pixel Y e -> Int #

alignment :: Pixel Y e -> Int #

peekElemOff :: Ptr (Pixel Y e) -> Int -> IO (Pixel Y e) #

pokeElemOff :: Ptr (Pixel Y e) -> Int -> Pixel Y e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Y e) #

pokeByteOff :: Ptr b -> Int -> Pixel Y e -> IO () #

peek :: Ptr (Pixel Y e) -> IO (Pixel Y e) #

poke :: Ptr (Pixel Y e) -> Pixel Y e -> IO () #

Storable e => Storable (Pixel HSIA e) # 

Methods

sizeOf :: Pixel HSIA e -> Int #

alignment :: Pixel HSIA e -> Int #

peekElemOff :: Ptr (Pixel HSIA e) -> Int -> IO (Pixel HSIA e) #

pokeElemOff :: Ptr (Pixel HSIA e) -> Int -> Pixel HSIA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSIA e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSIA e -> IO () #

peek :: Ptr (Pixel HSIA e) -> IO (Pixel HSIA e) #

poke :: Ptr (Pixel HSIA e) -> Pixel HSIA e -> IO () #

Storable e => Storable (Pixel HSI e) # 

Methods

sizeOf :: Pixel HSI e -> Int #

alignment :: Pixel HSI e -> Int #

peekElemOff :: Ptr (Pixel HSI e) -> Int -> IO (Pixel HSI e) #

pokeElemOff :: Ptr (Pixel HSI e) -> Int -> Pixel HSI e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel HSI e) #

pokeByteOff :: Ptr b -> Int -> Pixel HSI e -> IO () #

peek :: Ptr (Pixel HSI e) -> IO (Pixel HSI e) #

poke :: Ptr (Pixel HSI e) -> Pixel HSI e -> IO () #

Storable e => Storable (Pixel Gray e) # 

Methods

sizeOf :: Pixel Gray e -> Int #

alignment :: Pixel Gray e -> Int #

peekElemOff :: Ptr (Pixel Gray e) -> Int -> IO (Pixel Gray e) #

pokeElemOff :: Ptr (Pixel Gray e) -> Int -> Pixel Gray e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel Gray e) #

pokeByteOff :: Ptr b -> Int -> Pixel Gray e -> IO () #

peek :: Ptr (Pixel Gray e) -> IO (Pixel Gray e) #

poke :: Ptr (Pixel Gray e) -> Pixel Gray e -> IO () #

Storable e => Storable (Pixel CMYKA e) # 

Methods

sizeOf :: Pixel CMYKA e -> Int #

alignment :: Pixel CMYKA e -> Int #

peekElemOff :: Ptr (Pixel CMYKA e) -> Int -> IO (Pixel CMYKA e) #

pokeElemOff :: Ptr (Pixel CMYKA e) -> Int -> Pixel CMYKA e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYKA e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYKA e -> IO () #

peek :: Ptr (Pixel CMYKA e) -> IO (Pixel CMYKA e) #

poke :: Ptr (Pixel CMYKA e) -> Pixel CMYKA e -> IO () #

Storable e => Storable (Pixel CMYK e) # 

Methods

sizeOf :: Pixel CMYK e -> Int #

alignment :: Pixel CMYK e -> Int #

peekElemOff :: Ptr (Pixel CMYK e) -> Int -> IO (Pixel CMYK e) #

pokeElemOff :: Ptr (Pixel CMYK e) -> Int -> Pixel CMYK e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pixel CMYK e) #

pokeByteOff :: Ptr b -> Int -> Pixel CMYK e -> IO () #

peek :: Ptr (Pixel CMYK e) -> IO (Pixel CMYK e) #

poke :: Ptr (Pixel CMYK e) -> Pixel CMYK e -> IO () #

Storable (Pixel Binary Bit) # 
(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 

Methods

rnf :: Pixel cs e -> () #

data Pixel YCbCrA Source # 
data Pixel YCbCrA = PixelYCbCrA !e !e !e !e
data Pixel YCbCr Source # 
data Pixel YCbCr = PixelYCbCr !e !e !e
data Pixel RGBA Source # 
data Pixel RGBA = PixelRGBA !e !e !e !e
data Pixel RGB Source # 
data Pixel RGB = PixelRGB !e !e !e
data Pixel YA Source # 
data Pixel YA = PixelYA !e !e
data Pixel Y Source # 
data Pixel Y = PixelY !e
data Pixel HSIA Source # 
data Pixel HSIA = PixelHSIA !e !e !e !e
data Pixel HSI Source # 
data Pixel HSI = PixelHSI !e !e !e
data Pixel Gray Source # 
data Pixel Gray = PixelGray !e
data Pixel CMYKA Source # 
data Pixel CMYKA = PixelCMYKA !e !e !e !e !e
data Pixel CMYK Source # 
data Pixel CMYK = PixelCMYK !e !e !e !e
data Pixel Binary Source # 
data MVector s (Pixel cs e) # 
data MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
data Vector (Pixel cs e) # 
data Vector (Pixel cs e) = V_Pixel (Vector (Components cs 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, despite that separating image channels can be sometimes pretty useful, the same effect as above can be achieved in a much simpler and a 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)>

Instances

Enum Binary Source # 
Eq Binary Source # 

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Show Binary Source # 
ColorSpace Binary Bit Source # 
Readable [Image VS Binary Bit] [PBM] Source # 
Eq e => Eq (Pixel Binary e) Source # 

Methods

(==) :: Pixel Binary e -> Pixel Binary e -> Bool #

(/=) :: Pixel Binary e -> Pixel Binary e -> Bool #

Num (Pixel Binary Bit) Source # 
Ord e => Ord (Pixel Binary e) Source # 
Show (Pixel Binary Bit) Source # 
Storable (Pixel Binary Bit) Source # 
Writable (Image VS Binary Bit) TIF Source # 
Writable (Image VS Binary Bit) TGA Source # 
Writable (Image VS Binary Bit) PNG Source # 
Writable (Image VS Binary Bit) BMP Source # 
Readable (Image VS Binary Bit) TIF Source # 
Readable (Image VS Binary Bit) TGA Source # 
Readable (Image VS Binary Bit) PNG Source # 
Readable (Image VS Binary Bit) BMP Source # 
Readable (Image VS Binary Bit) PBM Source # 
data Pixel Binary Source # 
type Components Binary Bit Source # 

data Bit Source #

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

Instances

Eq Bit Source # 

Methods

(==) :: Bit -> Bit -> Bool #

(/=) :: Bit -> Bit -> Bool #

Num Bit Source # 

Methods

(+) :: Bit -> Bit -> Bit #

(-) :: Bit -> Bit -> Bit #

(*) :: Bit -> Bit -> Bit #

negate :: Bit -> Bit #

abs :: Bit -> Bit #

signum :: Bit -> Bit #

fromInteger :: Integer -> Bit #

Ord Bit Source # 

Methods

compare :: Bit -> Bit -> Ordering #

(<) :: Bit -> Bit -> Bool #

(<=) :: Bit -> Bit -> Bool #

(>) :: Bit -> Bit -> Bool #

(>=) :: Bit -> Bit -> Bool #

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Storable Bit Source # 

Methods

sizeOf :: Bit -> Int #

alignment :: Bit -> Int #

peekElemOff :: Ptr Bit -> Int -> IO Bit #

pokeElemOff :: Ptr Bit -> Int -> Bit -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bit #

pokeByteOff :: Ptr b -> Int -> Bit -> IO () #

peek :: Ptr Bit -> IO Bit #

poke :: Ptr Bit -> Bit -> IO () #

Elevator Bit Source # 
ColorSpace Binary Bit Source # 
Readable [Image VS Binary Bit] [PBM] Source # 
Num (Pixel Binary Bit) Source # 
Show (Pixel Binary Bit) Source # 
Storable (Pixel Binary Bit) Source # 
Writable (Image VS Binary Bit) TIF Source # 
Writable (Image VS Binary Bit) TGA Source # 
Writable (Image VS Binary Bit) PNG Source # 
Writable (Image VS Binary Bit) BMP Source # 
Readable (Image VS Binary Bit) TIF Source # 
Readable (Image VS Binary Bit) TGA Source # 
Readable (Image VS Binary Bit) PNG Source # 
Readable (Image VS Binary Bit) BMP Source # 
Readable (Image VS Binary Bit) PBM Source # 
data Vector Bit # 
data MVector s Bit # 
type Components Binary Bit Source # 

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 :: (Eq (Pixel cs e), Num (Pixel cs e)) => Pixel cs e -> Pixel Binary Bit Source #

Convert any pixel to binary pixel.

fromPixelBinary :: Pixel Binary Bit -> Pixel Y Word8 Source #

Convert a Binary pixel to Luma pixel

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

Convert any image to binary image.

fromImageBinary :: (Array arr Binary Bit, Array arr Y Word8) => Image arr Binary Bit -> Image arr Y Word8 Source #

Convert a Binary image to Luma image

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.

The Foldable and Traversable instances traverse the real part first.

Constructors

~a :+ ~a infix 6

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

Instances

Monad Complex 

Methods

(>>=) :: Complex a -> (a -> Complex b) -> Complex b #

(>>) :: Complex a -> Complex b -> Complex b #

return :: a -> Complex a #

fail :: String -> Complex a #

Functor Complex 

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Applicative Complex 

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Foldable Complex 

Methods

fold :: Monoid m => Complex m -> m #

foldMap :: Monoid m => (a -> m) -> Complex a -> m #

foldr :: (a -> b -> b) -> b -> Complex a -> b #

foldr' :: (a -> b -> b) -> b -> Complex a -> b #

foldl :: (b -> a -> b) -> b -> Complex a -> b #

foldl' :: (b -> a -> b) -> b -> Complex a -> b #

foldr1 :: (a -> a -> a) -> Complex a -> a #

foldl1 :: (a -> a -> a) -> Complex a -> a #

toList :: Complex a -> [a] #

null :: Complex a -> Bool #

length :: Complex a -> Int #

elem :: Eq a => a -> Complex a -> Bool #

maximum :: Ord a => Complex a -> a #

minimum :: Ord a => Complex a -> a #

sum :: Num a => Complex a -> a #

product :: Num a => Complex a -> a #

Traversable Complex 

Methods

traverse :: Applicative f => (a -> f b) -> Complex a -> f (Complex b) #

sequenceA :: Applicative f => Complex (f a) -> f (Complex a) #

mapM :: Monad m => (a -> m b) -> Complex a -> m (Complex b) #

sequence :: Monad m => Complex (m a) -> m (Complex a) #

Generic1 Complex 

Associated Types

type Rep1 (Complex :: * -> *) :: * -> * #

Methods

from1 :: Complex a -> Rep1 Complex a #

to1 :: Rep1 Complex a -> Complex a #

Representable Complex 

Associated Types

type Rep (Complex :: * -> *) :: * #

Methods

tabulate :: (Rep Complex -> a) -> Complex a #

index :: Complex a -> Rep Complex -> a #

Additive Complex 

Methods

zero :: Num a => Complex a #

(^+^) :: Num a => Complex a -> Complex a -> Complex a #

(^-^) :: Num a => Complex a -> Complex a -> Complex a #

lerp :: Num a => a -> Complex a -> Complex a -> Complex a #

liftU2 :: (a -> a -> a) -> Complex a -> Complex a -> Complex a #

liftI2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

Affine Complex 

Associated Types

type Diff (Complex :: * -> *) :: * -> * #

Methods

(.-.) :: Num a => Complex a -> Complex a -> Diff Complex a #

(.+^) :: Num a => Complex a -> Diff Complex a -> Complex a #

(.-^) :: Num a => Complex a -> Diff Complex a -> Complex a #

Complicated Complex 

Methods

_e :: Functor f => (a -> f a) -> Complex a -> f (Complex a) #

_i :: Functor f => (a -> f a) -> Complex a -> f (Complex a) #

(RealFloat a, Unbox a) => Vector Vector (Complex a) 
(RealFloat a, Unbox a) => MVector MVector (Complex a) 
Eq a => Eq (Complex a) 

Methods

(==) :: Complex a -> Complex a -> Bool #

(/=) :: Complex a -> Complex a -> Bool #

RealFloat a => Floating (Complex a) 

Methods

pi :: Complex a #

exp :: Complex a -> Complex a #

log :: Complex a -> Complex a #

sqrt :: Complex a -> Complex a #

(**) :: Complex a -> Complex a -> Complex a #

logBase :: Complex a -> Complex a -> Complex a #

sin :: Complex a -> Complex a #

cos :: Complex a -> Complex a #

tan :: Complex a -> Complex a #

asin :: Complex a -> Complex a #

acos :: Complex a -> Complex a #

atan :: Complex a -> Complex a #

sinh :: Complex a -> Complex a #

cosh :: Complex a -> Complex a #

tanh :: Complex a -> Complex a #

asinh :: Complex a -> Complex a #

acosh :: Complex a -> Complex a #

atanh :: Complex a -> Complex a #

log1p :: Complex a -> Complex a #

expm1 :: Complex a -> Complex a #

log1pexp :: Complex a -> Complex a #

log1mexp :: Complex a -> Complex a #

RealFloat a => Fractional (Complex a) 

Methods

(/) :: Complex a -> Complex a -> Complex a #

recip :: Complex a -> Complex a #

fromRational :: Rational -> Complex a #

Data a => Data (Complex a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Complex a -> c (Complex a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Complex a) #

toConstr :: Complex a -> Constr #

dataTypeOf :: Complex a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Complex a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Complex a)) #

gmapT :: (forall b. Data b => b -> b) -> Complex a -> Complex a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Complex a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Complex a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) #

RealFloat a => Num (Complex a) 

Methods

(+) :: Complex a -> Complex a -> Complex a #

(-) :: Complex a -> Complex a -> Complex a #

(*) :: Complex a -> Complex a -> Complex a #

negate :: Complex a -> Complex a #

abs :: Complex a -> Complex a #

signum :: Complex a -> Complex a #

fromInteger :: Integer -> Complex a #

Read a => Read (Complex a) 
Show a => Show (Complex a) 

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Generic (Complex a) 

Associated Types

type Rep (Complex a) :: * -> * #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

(Default a, RealFloat a) => Default (Complex a) 

Methods

def :: Complex a #

Storable a => Storable (Complex a) 

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

peekElemOff :: Ptr (Complex a) -> Int -> IO (Complex a) #

pokeElemOff :: Ptr (Complex a) -> Int -> Complex a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Complex a) #

pokeByteOff :: Ptr b -> Int -> Complex a -> IO () #

peek :: Ptr (Complex a) -> IO (Complex a) #

poke :: Ptr (Complex a) -> Complex a -> IO () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

(RealFloat a, Unbox a) => Unbox (Complex a) 
type Rep1 Complex 
type Rep Complex 
type Diff Complex 
data MVector s (Complex a) 
data MVector s (Complex a) = MV_Complex (MVector s (a, a))
type Rep (Complex a) 
type Index (Complex a) 
type Index (Complex a) = Int
data Vector (Complex a) 
data Vector (Complex a) = V_Complex (Vector (a, a))

(+:) :: Applicative (Pixel 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 :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source #

Extracts the real part of a complex pixel.

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

Extracts the imaginary part of a complex pixel.

Polar form

mkPolar :: (Applicative (Pixel 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 :: (Applicative (Pixel 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 :: (Applicative (Pixel 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 :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source #

The nonnegative magnitude of a complex pixel.

phase :: (Applicative (Pixel 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 :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs (Complex e) Source #

The conjugate of a complex pixel.

Re-exports

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8 
Num Word8 
Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Default Word8 

Methods

def :: Word8 #

Unpackable Word8

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

Associated Types

type StorageType Word8 :: *

Methods

outAlloc :: Word8 -> Int -> ST s (STVector s (StorageType Word8))

allocTempBuffer :: Word8 -> STVector s (StorageType Word8) -> Int -> ST s (STVector s Word8)

offsetStride :: Word8 -> Int -> Int -> (Int, Int)

mergeBackTempBuffer :: Word8 -> Endianness -> STVector s Word8 -> Int -> Int -> Word32 -> Int -> STVector s (StorageType Word8) -> ST s ()

TiffSaveable Pixel8 
JpgEncodable Pixel8 

Methods

additionalBlocks :: Image Pixel8 -> [JpgFrame]

componentsOfColorSpace :: Image Pixel8 -> [JpgComponent]

encodingState :: Int -> Image Pixel8 -> Vector EncoderState

imageHuffmanTables :: Image Pixel8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)]

scanSpecificationOfColorSpace :: Image Pixel8 -> [JpgScanSpecification]

quantTableSpec :: Image Pixel8 -> Int -> [JpgQuantTableSpec]

maximumSubSamplingOf :: Image Pixel8 -> Int

BmpEncodable Pixel8 
TgaSaveable Pixel8 
PngSavable Pixel8 
Pixel Pixel8 
LumaPlaneExtractable Pixel8 
PackeablePixel Pixel8 
Storable Word8 

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8 
FiniteBits Word8 
NFData Word8 

Methods

rnf :: Word8 -> () #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Unbox Word8 
Elt Word8 

Methods

touch :: Word8 -> IO () #

zero :: Word8 #

one :: 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 
IArray UArray Word8 

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) #

numElements :: Ix i => UArray i Word8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8

Vector Vector Word8 
Source B Word8

Read elements from a ByteString.

Associated Types

data Array B sh Word8 :: * #

Methods

extent :: Shape sh => Array B sh Word8 -> sh #

index :: Shape sh => Array B sh Word8 -> sh -> Word8 #

unsafeIndex :: Shape sh => Array B sh Word8 -> sh -> Word8 #

linearIndex :: Shape sh => Array B sh Word8 -> Int -> Word8 #

unsafeLinearIndex :: Shape sh => Array B sh Word8 -> Int -> Word8 #

deepSeqArray :: Shape sh => Array B sh Word8 -> b -> b #

MVector MVector Word8 
Structured B Word8 b 

Associated Types

type TR B :: * #

Methods

smap :: Shape sh => (Word8 -> b) -> Array B sh Word8 -> Array (TR B) sh b #

szipWith :: (Shape sh, Source r c) => (c -> Word8 -> b) -> Array r sh c -> Array B sh Word8 -> Array (TR B) sh b #

MArray (STUArray s) Word8 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

Writable [(GifDelay, Image VS RGB Word8)] [GIF] Source # 
Readable [Image VS RGBA Word8] [GIF] Source # 
Readable [Image VS RGB Word8] [GIF] Source # 
Readable [Image VS RGB Word8] [PPM] Source # 
Readable [Image VS Y Word8] [PGM] Source # 
Read sh => Read (Array B sh Word8) 
Show sh => Show (Array B sh Word8) 

Methods

showsPrec :: Int -> Array B sh Word8 -> ShowS #

show :: Array B sh Word8 -> String #

showList :: [Array B sh Word8] -> ShowS #

Writable (Image VS YCbCr Word8) TIF Source # 
Writable (Image VS YCbCr Word8) JPG Source # 
Writable (Image VS RGBA Word8) TIF Source # 
Writable (Image VS RGBA Word8) TGA Source # 
Writable (Image VS RGBA Word8) PNG Source # 
Writable (Image VS RGBA Word8) BMP Source # 
Writable (Image VS RGB Word8) TIF Source # 
Writable (Image VS RGB Word8) TGA Source # 
Writable (Image VS RGB Word8) PNG Source # 
Writable (Image VS RGB Word8) JPG Source # 
Writable (Image VS RGB Word8) GIF Source # 
Writable (Image VS RGB Word8) BMP Source # 
Writable (Image VS YA Word8) TIF Source # 
Writable (Image VS YA Word8) PNG Source # 
Writable (Image VS Y Word8) TIF Source # 
Writable (Image VS Y Word8) TGA Source # 
Writable (Image VS Y Word8) PNG Source # 
Writable (Image VS Y Word8) JPG Source # 
Writable (Image VS Y Word8) BMP Source # 
Writable (Image VS CMYK Word8) TIF Source # 
Writable (Image VS CMYK Word8) JPG Source # 
Readable (Image VS YCbCr Word8) JPG Source # 
Readable (Image VS RGBA Word8) TIF Source # 
Readable (Image VS RGBA Word8) TGA Source # 
Readable (Image VS RGBA Word8) PNG Source # 
Readable (Image VS RGBA Word8) GIF Source # 
Readable (Image VS RGBA Word8) BMP Source # 
Readable (Image VS RGB Word8) TIF Source # 
Readable (Image VS RGB Word8) TGA Source # 
Readable (Image VS RGB Word8) PNG Source # 
Readable (Image VS RGB Word8) JPG Source # 
Readable (Image VS RGB Word8) GIF Source # 
Readable (Image VS RGB Word8) BMP Source # 
Readable (Image VS RGB Word8) PPM Source # 
Readable (Image VS YA Word8) TIF Source # 
Readable (Image VS YA Word8) PNG Source # 
Readable (Image VS YA Word8) JPG Source # 
Readable (Image VS Y Word8) TIF Source # 
Readable (Image VS Y Word8) TGA Source # 
Readable (Image VS Y Word8) PNG Source # 
Readable (Image VS Y Word8) JPG Source # 
Readable (Image VS Y Word8) BMP Source # 
Readable (Image VS Y Word8) PGM Source # 
Readable (Image VS CMYK Word8) TIF Source # 
Readable (Image VS CMYK Word8) JPG Source # 
type StorageType Word8 
type StorageType Word8 = Word8
type PixelBaseComponent Pixel8 
type PackedRepresentation Pixel8 
type Unsigned Word8 
type Signed Word8 
data Vector Word8 
data MVector s Word8 
data Array B sh Word8 

data Word16 :: * #

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16 
Num Word16 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
Lift Word16 

Methods

lift :: Word16 -> Q Exp #

Default Word16 

Methods

def :: Word16 #

Unpackable Word16 

Associated Types

type StorageType Word16 :: *

Methods

outAlloc :: Word16 -> Int -> ST s (STVector s (StorageType Word16))

allocTempBuffer :: Word16 -> STVector s (StorageType Word16) -> Int -> ST s (STVector s Word8)

offsetStride :: Word16 -> Int -> Int -> (Int, Int)

mergeBackTempBuffer :: Word16 -> Endianness -> STVector s Word8 -> Int -> Int -> Word32 -> Int -> STVector s (StorageType Word16) -> ST s ()

TiffSaveable Pixel16 
PngSavable Pixel16 
Pixel Pixel16 
LumaPlaneExtractable Pixel16 
PackeablePixel Pixel16 
Storable Word16 
Bits Word16 
FiniteBits Word16 
NFData Word16 

Methods

rnf :: Word16 -> () #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Prim Word16 
Unbox Word16 
Elt Word16 

Methods

touch :: Word16 -> IO () #

zero :: Word16 #

one :: Word16 #

Decimable Pixel16 Pixel8 
TransparentPixel PixelYA16 Pixel16 
ColorConvertible Pixel8 Pixel16 
ColorConvertible Pixel16 PixelYA16 
ColorConvertible Pixel16 PixelRGB16 
ColorConvertible Pixel16 PixelRGBA16 
IArray UArray Word16 

Methods

bounds :: Ix i => UArray i Word16 -> (i, i) #

numElements :: Ix i => UArray i Word16 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word16)] -> UArray i Word16

unsafeAt :: Ix i => UArray i Word16 -> Int -> Word16

unsafeReplace :: Ix i => UArray i Word16 -> [(Int, Word16)] -> UArray i Word16

unsafeAccum :: Ix i => (Word16 -> e' -> Word16) -> UArray i Word16 -> [(Int, e')] -> UArray i Word16

unsafeAccumArray :: Ix i => (Word16 -> e' -> Word16) -> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16

Vector Vector Word16 
MVector MVector Word16 
MArray (STUArray s) Word16 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word16 -> ST s Int

newArray :: Ix i => (i, i) -> Word16 -> ST s (STUArray s i Word16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16)

unsafeRead :: Ix i => STUArray s i Word16 -> Int -> ST s Word16

unsafeWrite :: Ix i => STUArray s i Word16 -> Int -> Word16 -> ST s ()

Readable [Image VS RGB Word16] [PPM] Source # 
Readable [Image VS Y Word16] [PGM] Source # 
Writable (Image VS RGBA Word16) TIF Source # 
Writable (Image VS RGBA Word16) PNG Source # 
Writable (Image VS RGB Word16) TIF Source # 
Writable (Image VS RGB Word16) PNG Source # 
Writable (Image VS YA Word16) TIF Source # 
Writable (Image VS YA Word16) PNG Source # 
Writable (Image VS Y Word16) TIF Source # 
Writable (Image VS Y Word16) PNG Source # 
Writable (Image VS CMYK Word16) TIF Source # 
Readable (Image VS RGBA Word16) TIF Source # 
Readable (Image VS RGBA Word16) PNG Source # 
Readable (Image VS RGB Word16) TIF Source # 
Readable (Image VS RGB Word16) PNG Source # 
Readable (Image VS RGB Word16) PPM Source # 
Readable (Image VS YA Word16) TIF Source # 
Readable (Image VS YA Word16) PNG Source # 
Readable (Image VS Y Word16) TIF Source # 
Readable (Image VS Y Word16) PNG Source # 
Readable (Image VS Y Word16) PGM Source # 
Readable (Image VS CMYK Word16) TIF Source # 
type StorageType Word16 
type StorageType Word16 = Word16
type PixelBaseComponent Pixel16 
type PackedRepresentation Pixel16 
type Unsigned Word16 
type Signed Word16 
data Vector Word16 
data MVector s Word16 

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32 
Num Word32 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
Lift Word32 

Methods

lift :: Word32 -> Q Exp #

Default Word32 

Methods

def :: Word32 #

Unpackable Word32 

Associated Types

type StorageType Word32 :: *

Methods

outAlloc :: Word32 -> Int -> ST s (STVector s (StorageType Word32))

allocTempBuffer :: Word32 -> STVector s (StorageType Word32) -> Int -> ST s (STVector s Word8)

offsetStride :: Word32 -> Int -> Int -> (Int, Int)

mergeBackTempBuffer :: Word32 -> Endianness -> STVector s Word8 -> Int -> Int -> Word32 -> Int -> STVector s (StorageType Word32) -> ST s ()

Pixel Pixel32 
LumaPlaneExtractable Pixel32 
PackeablePixel Pixel32 
Storable Word32 
Bits Word32 
FiniteBits Word32 
NFData Word32 

Methods

rnf :: Word32 -> () #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Unbox Word32 
Elt Word32 

Methods

touch :: Word32 -> IO () #

zero :: Word32 #

one :: Word32 #

IArray UArray Word32 

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) #

numElements :: Ix i => UArray i Word32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32

Vector Vector Word32 
MVector MVector Word32 
MArray (STUArray s) Word32 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

type StorageType Word32 
type StorageType Word32 = Word32
type PixelBaseComponent Pixel32 
type PackedRepresentation Pixel32 
type Unsigned Word32 
type Signed Word32 
data Vector Word32 
data MVector s Word32 

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Integral Word64 
Num Word64 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
Lift Word64 

Methods

lift :: Word64 -> Q Exp #

Default Word64 

Methods

def :: Word64 #

Storable Word64 
Bits Word64 
FiniteBits Word64 
NFData Word64 

Methods

rnf :: Word64 -> () #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Prim Word64 
Unbox Word64 
Elt Word64 

Methods

touch :: Word64 -> IO () #

zero :: Word64 #

one :: Word64 #

IArray UArray Word64 

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) #

numElements :: Ix i => UArray i Word64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64

Vector Vector Word64 
MVector MVector Word64 
MArray (STUArray s) Word64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

type Unsigned Word64 
type Signed Word64 
data Vector Word64 
data MVector s Word64 

Orphan instances

Elevator Double Source # 
Elevator Float Source # 
Elevator Int Source # 
Elevator Int8 Source # 
Elevator Int16 Source # 
Elevator Int32 Source # 
Elevator Int64 Source # 
Elevator Word Source # 
Elevator Word8 Source # 
Elevator Word16 Source # 
Elevator Word32 Source # 
Elevator Word64 Source # 
ToYCbCrA RGBA Source # 
ToYCbCr RGB Source # 
ToRGBA YCbCrA Source # 
ToRGBA YA Source # 
ToRGBA HSIA Source # 
ToRGBA CMYKA Source # 
ToRGB YCbCr Source # 
ToRGB Y Source # 
ToRGB HSI Source # 
ToRGB CMYK Source # 
ToYA YCbCrA Source # 
ToYA RGBA Source # 
ToYA HSIA Source # 
ToY YCbCr Source # 
ToY RGB Source #

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

ToY HSI Source # 
ToY Gray Source # 
ToY CMYK Source # 
ToHSIA RGBA Source # 
ToHSIA YA Source # 
ToHSI RGB Source # 
ToHSI Y Source # 
ToCMYKA RGBA Source # 
ToCMYK RGB Source # 
(Num e, Elevator e, RealFloat e) => Elevator (Complex e) Source #