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

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

Graphics.Image.ColorSpace

Contents

Description

 
Synopsis

Pixels

Family of Pixels

Pixel is a type family for all available color spaces. Below is the listed of all class instances, that pixels are installed in, as well as all pixel constructors.

>>> :t (PixelY 0) -- Black pixel in Luma
(PixelY 0) :: Num e => Pixel Y e
>>> PixelRGB 255 0 0 :: Pixel RGB Word8 -- Red pixel in RGB
<RGB:(255|0|0)>
>>> PixelRGB 1 0 0 :: Pixel RGB Double -- Same red pixel in RGB with Double precision.
<RGB:(1.0|0.0|0.0)>
>>> (PixelRGB 255 0 0 :: Pixel RGB Word8) == (toWord8 <$> (PixelRGB 1 0 0 :: Pixel RGB Double))
True

data family Pixel cs e :: * Source #

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

Instances
Array arr X Bit => Thresholding Pixel (Image arr) arr Source # 
Instance details

Defined in Graphics.Image.Processing.Binary

Methods

(!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source #

(!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Pixel cs e -> Image arr cs e -> Image arr cs Bit Source #

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

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

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

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

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

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

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

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

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

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

ColorSpace cs e => Vector Vector (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface.Vector.Unboxing

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Pixel cs e) -> m (Vector (Pixel cs e)) #

basicUnsafeThaw :: PrimMonad m => Vector (Pixel cs e) -> m (Mutable Vector (PrimState m) (Pixel cs e)) #

basicLength :: Vector (Pixel cs e) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Pixel cs e) -> Vector (Pixel cs e) #

basicUnsafeIndexM :: Monad m => Vector (Pixel cs e) -> Int -> m (Pixel cs e) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Pixel cs e) -> Vector (Pixel cs e) -> m () #

elemseq :: Vector (Pixel cs e) -> Pixel cs e -> b -> b #

ColorSpace cs e => MVector MVector (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface.Vector.Unboxing

Methods

basicLength :: MVector s (Pixel cs e) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Pixel cs e) -> MVector s (Pixel cs e) #

basicOverlaps :: MVector s (Pixel cs e) -> MVector s (Pixel cs e) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Pixel cs e)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Pixel cs e -> m (MVector (PrimState m) (Pixel cs e)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> Int -> m (Pixel cs e) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> Int -> Pixel cs e -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> Pixel cs e -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> MVector (PrimState m) (Pixel cs e) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> MVector (PrimState m) (Pixel cs e) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Pixel cs e) -> Int -> m (MVector (PrimState m) (Pixel cs e)) #

Monad (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

return :: a -> Pixel X a #

fail :: String -> Pixel X a #

Functor (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Functor (Pixel YCbCr) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Functor (Pixel YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Functor (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Functor (Pixel RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Functor (Pixel RGB) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Functor (Pixel HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Functor (Pixel HSI) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Functor (Pixel CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Functor (Pixel CMYK) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Functor (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

Applicative (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

pure :: a -> Pixel YCbCrA a #

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

liftA2 :: (a -> b -> c) -> Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA c #

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

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

Applicative (Pixel YCbCr) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

pure :: a -> Pixel YCbCr a #

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

liftA2 :: (a -> b -> c) -> Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr c #

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

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

Applicative (Pixel YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

pure :: a -> Pixel YA a #

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

liftA2 :: (a -> b -> c) -> Pixel YA a -> Pixel YA b -> Pixel YA c #

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

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

Applicative (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

pure :: a -> Pixel Y a #

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

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

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

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

Applicative (Pixel RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

pure :: a -> Pixel RGBA a #

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

liftA2 :: (a -> b -> c) -> Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA c #

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

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

Applicative (Pixel RGB) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

pure :: a -> Pixel RGB a #

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

liftA2 :: (a -> b -> c) -> Pixel RGB a -> Pixel RGB b -> Pixel RGB c #

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

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

Applicative (Pixel HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

pure :: a -> Pixel HSIA a #

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

liftA2 :: (a -> b -> c) -> Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA c #

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

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

Applicative (Pixel HSI) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

pure :: a -> Pixel HSI a #

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

liftA2 :: (a -> b -> c) -> Pixel HSI a -> Pixel HSI b -> Pixel HSI c #

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

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

Applicative (Pixel CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

pure :: a -> Pixel CMYKA a #

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

liftA2 :: (a -> b -> c) -> Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA c #

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

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

Applicative (Pixel CMYK) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

pure :: a -> Pixel CMYK a #

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

liftA2 :: (a -> b -> c) -> Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK c #

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

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

Applicative (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

pure :: a -> Pixel X a #

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

liftA2 :: (a -> b -> c) -> Pixel X a -> Pixel X b -> Pixel X c #

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

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

Foldable (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Foldable (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

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

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

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

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

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

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

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

null :: Pixel X a -> Bool #

length :: Pixel X a -> Int #

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

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

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

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

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

Array arr X Bit => Thresholding (Image arr) Pixel arr Source # 
Instance details

Defined in Graphics.Image.Processing.Binary

Methods

(!==!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source #

(!/=!) :: (Applicative (Pixel cs), Array arr cs e, Array arr cs Bit) => Image arr cs e -> Pixel cs e -> Image arr cs Bit Source #

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

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

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

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

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

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

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

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

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

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

(ColorSpace cs e, Bounded e) => Bounded (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

Eq e => Eq (Pixel YCbCrA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Eq e => Eq (Pixel YCbCr e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Eq e => Eq (Pixel YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Eq e => Eq (Pixel Y e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Eq e => Eq (Pixel RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Eq e => Eq (Pixel RGB e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Eq e => Eq (Pixel HSIA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Eq e => Eq (Pixel HSI e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Eq e => Eq (Pixel CMYKA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Eq e => Eq (Pixel CMYK e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Eq e => Eq (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

(ColorSpace cs e, Floating e) => Floating (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface

Methods

pi :: Pixel cs e #

exp :: Pixel cs e -> Pixel cs e #

log :: Pixel cs e -> Pixel cs e #

sqrt :: Pixel cs e -> Pixel cs e #

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

logBase :: Pixel cs e -> Pixel cs e -> Pixel cs e #

sin :: Pixel cs e -> Pixel cs e #

cos :: Pixel cs e -> Pixel cs e #

tan :: Pixel cs e -> Pixel cs e #

asin :: Pixel cs e -> Pixel cs e #

acos :: Pixel cs e -> Pixel cs e #

atan :: Pixel cs e -> Pixel cs e #

sinh :: Pixel cs e -> Pixel cs e #

cosh :: Pixel cs e -> Pixel cs e #

tanh :: Pixel cs e -> Pixel cs e #

asinh :: Pixel cs e -> Pixel cs e #

acosh :: Pixel cs e -> Pixel cs e #

atanh :: Pixel cs e -> Pixel cs e #

log1p :: Pixel cs e -> Pixel cs e #

expm1 :: Pixel cs e -> Pixel cs e #

log1pexp :: Pixel cs e -> Pixel cs e #

log1mexp :: Pixel cs e -> Pixel cs e #

(ColorSpace cs e, Fractional e) => Fractional (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface

Methods

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

recip :: Pixel cs e -> Pixel cs e #

fromRational :: Rational -> Pixel cs e #

ColorSpace cs e => Num (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface

Methods

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

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

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

negate :: Pixel cs e -> Pixel cs e #

abs :: Pixel cs e -> Pixel cs e #

signum :: Pixel cs e -> Pixel cs e #

fromInteger :: Integer -> Pixel cs e #

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

Defined in Graphics.Image.ColorSpace.Y

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 X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

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

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

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

max :: Pixel X e -> Pixel X e -> Pixel X e #

min :: Pixel X e -> Pixel X e -> Pixel X e #

Show e => Show (Pixel YCbCrA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Show e => Show (Pixel YCbCr e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

show :: Pixel YCbCr e -> String #

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

Show e => Show (Pixel YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

show :: Pixel YA e -> String #

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

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

Defined in Graphics.Image.ColorSpace.Y

Methods

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

show :: Pixel Y e -> String #

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

Show e => Show (Pixel RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

show :: Pixel RGBA e -> String #

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

Show e => Show (Pixel RGB e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

show :: Pixel RGB e -> String #

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

Show e => Show (Pixel HSIA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

show :: Pixel HSIA e -> String #

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

Show e => Show (Pixel HSI e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

show :: Pixel HSI e -> String #

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

Show e => Show (Pixel CMYKA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

show :: Pixel CMYKA e -> String #

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

Show e => Show (Pixel CMYK e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

show :: Pixel CMYK e -> String #

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

Show e => Show (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

show :: Pixel X e -> String #

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

Storable e => Storable (Pixel YCbCrA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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 YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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 RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 HSIA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 CMYKA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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 e => Storable (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

sizeOf :: Pixel X e -> Int #

alignment :: Pixel X e -> Int #

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

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

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

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

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

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

Bits (Pixel X Bit) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

(Foldable (Pixel cs), NFData e) => NFData (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface

Methods

rnf :: Pixel cs e -> () #

ColorSpace cs e => Unbox (Pixel cs e) Source #

Unboxing of a Pixel.

Instance details

Defined in Graphics.Image.Interface.Vector.Unboxing

(ColorSpace cs e, Elt e, Num (Pixel cs e)) => Elt (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface.Repa.Generic

Methods

touch :: Pixel cs e -> IO () #

zero :: Pixel cs e #

one :: Pixel cs e #

data Pixel YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

data Pixel YCbCrA e = PixelYCbCrA !e !e !e !e
data Pixel YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

data Pixel YCbCr e = PixelYCbCr !e !e !e
data Pixel YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

data Pixel YA e = PixelYA !e !e
newtype Pixel Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

newtype Pixel Y e = PixelY e
data Pixel RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

data Pixel RGBA e = PixelRGBA !e !e !e !e
data Pixel RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

data Pixel RGB e = PixelRGB !e !e !e
data Pixel HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

data Pixel HSIA e = PixelHSIA !e !e !e !e
data Pixel HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

data Pixel HSI e = PixelHSI !e !e !e
data Pixel CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

data Pixel CMYKA e = PixelCMYKA !e !e !e !e !e
data Pixel CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

data Pixel CMYK e = PixelCMYK !e !e !e !e
newtype Pixel X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

newtype Pixel X e = PixelX {}
newtype MVector s (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface.Vector.Unboxing

newtype MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
newtype Vector (Pixel cs e) Source # 
Instance details

Defined in Graphics.Image.Interface.Vector.Unboxing

newtype Vector (Pixel cs e) = V_Pixel (Vector (Components cs e))

Luma (gray scale)

Conversion to Luma from other color spaces.

toPixelY :: ToY cs e => Pixel cs e -> Pixel Y Double Source #

Convert a pixel to Luma pixel.

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

Convert an image to Luma image.

toPixelYA :: ToYA cs e => Pixel cs e -> Pixel YA Double Source #

Convert a pixel to Luma pixel with Alpha.

toImageYA :: (ToYA cs e, Array arr cs e, Array arr YA Double) => Image arr cs e -> Image arr YA Double Source #

Convert an image to Luma image with Alpha.

RGB

Conversion to RGB from other color spaces.

toPixelRGB :: ToRGB cs e => Pixel cs e -> Pixel RGB Double Source #

Convert to an RGB pixel.

toImageRGB :: (ToRGB cs e, Array arr cs e, Array arr RGB Double) => Image arr cs e -> Image arr RGB Double Source #

Convert to an RGB image.

toPixelRGBA :: ToRGBA cs e => Pixel cs e -> Pixel RGBA Double Source #

Convert to an RGBA pixel.

toImageRGBA :: (ToRGBA cs e, Array arr cs e, Array arr RGBA Double) => Image arr cs e -> Image arr RGBA Double Source #

Convert to an RGBA image.

HSI

Conversion to HSI from other color spaces.

toPixelHSI :: ToHSI cs e => Pixel cs e -> Pixel HSI Double Source #

Convert to an HSI pixel.

toImageHSI :: (ToHSI cs e, Array arr cs e, Array arr HSI Double) => Image arr cs e -> Image arr HSI Double Source #

Convert to an HSI image.

toPixelHSIA :: ToHSIA cs e => Pixel cs e -> Pixel HSIA Double Source #

Convert to an HSIA pixel.

toImageHSIA :: (ToHSIA cs e, Array arr cs e, Array arr HSIA Double) => Image arr cs e -> Image arr HSIA Double Source #

Convert to an HSIA image.

CMYK

Conversion to CMYK from other color spaces.

toPixelCMYK :: ToCMYK cs e => Pixel cs e -> Pixel CMYK Double Source #

Convert to a CMYK pixel.

toImageCMYK :: (ToCMYK cs e, Array arr cs e, Array arr CMYK Double) => Image arr cs e -> Image arr CMYK Double Source #

Convert to a CMYK image.

toPixelCMYKA :: ToCMYKA cs e => Pixel cs e -> Pixel CMYKA Double Source #

Convert to a CMYKA pixel.

toImageCMYKA :: (ToCMYKA cs e, Array arr cs e, Array arr CMYKA Double) => Image arr cs e -> Image arr CMYKA Double Source #

Convert to a CMYKA image.

YCbCr

Conversion to YCbCr from other color spaces.

toPixelYCbCr :: ToYCbCr cs e => Pixel cs e -> Pixel YCbCr Double Source #

Convert to an YCbCr pixel.

toImageYCbCr :: (ToYCbCr cs e, Array arr cs e, Array arr YCbCr Double) => Image arr cs e -> Image arr YCbCr Double Source #

Convert to an YCbCr image.

toPixelYCbCrA :: ToYCbCrA cs e => Pixel cs e -> Pixel YCbCrA Double Source #

Convert to an YCbCrA pixel.

toImageYCbCrA :: (ToYCbCrA cs e, Array arr cs e, Array arr YCbCrA Double) => Image arr cs e -> Image arr YCbCrA Double Source #

Convert to an YCbCrA image.

Binary

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

toPixelBinary :: ColorSpace cs e => Pixel cs e -> Pixel X Bit Source #

Convert to a Binary pixel.

fromPixelBinary :: Pixel X Bit -> Pixel Y Word8 Source #

Convert a Binary pixel to Luma pixel

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

Convert to a Binary image.

fromImageBinary :: (Array arr X Bit, Array arr Y Word8) => Image arr X Bit -> Image arr Y Word8 Source #

Convert a Binary image to Luma image

newtype Bit Source #

Under the hood, binary pixels are represented as Word8, but can only take values of 0 or 1. Use zero/one to construct a bit and on/off to construct a binary pixel.

Constructors

Bit Word8 
Instances
Eq Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

Methods

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

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

Num Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

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 #

Show Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Storable Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

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

Bits Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

Methods

(.&.) :: Bit -> Bit -> Bit #

(.|.) :: Bit -> Bit -> Bit #

xor :: Bit -> Bit -> Bit #

complement :: Bit -> Bit #

shift :: Bit -> Int -> Bit #

rotate :: Bit -> Int -> Bit #

zeroBits :: Bit #

bit :: Int -> Bit #

setBit :: Bit -> Int -> Bit #

clearBit :: Bit -> Int -> Bit #

complementBit :: Bit -> Int -> Bit #

testBit :: Bit -> Int -> Bool #

bitSizeMaybe :: Bit -> Maybe Int #

bitSize :: Bit -> Int #

isSigned :: Bit -> Bool #

shiftL :: Bit -> Int -> Bit #

unsafeShiftL :: Bit -> Int -> Bit #

shiftR :: Bit -> Int -> Bit #

unsafeShiftR :: Bit -> Int -> Bit #

rotateL :: Bit -> Int -> Bit #

rotateR :: Bit -> Int -> Bit #

popCount :: Bit -> Int #

Unbox Bit Source #

Unboxing of a Bit.

Instance details

Defined in Graphics.Image.ColorSpace.Binary

Elt Bit Source # 
Instance details

Defined in Graphics.Image.Interface.Repa.Generic

Methods

touch :: Bit -> IO () #

zero :: Bit #

one :: Bit #

Elevator Bit Source #

Values: 0 and 1

Instance details

Defined in Graphics.Image.ColorSpace.Binary

Vector Vector Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

MVector MVector Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

ToRGBA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Readable [Image VS X Bit] (Seq PBM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Bits (Pixel X Bit) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

Writable (Image VS X Bit) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) PBM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS X Bit) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

newtype Vector Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

newtype MVector s Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

newtype MVector s Bit = MV_Bit (MVector s Word8)

on :: Pixel X Bit Source #

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

off :: Pixel X Bit Source #

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

isOn :: Pixel X Bit -> Bool Source #

Test if Pixel's value is on.

isOff :: Pixel X Bit -> Bool Source #

Test if Pixel's value is off.

fromBool :: Bool -> Pixel X Bit Source #

Convert a Bool to a binary pixel.

>>> isOn (fromBool True)
True

toNum :: Num a => Bit -> a Source #

fromNum :: (Eq a, Num a) => a -> Bit Source #

Complex

Rectangular form

data Complex a #

Complex numbers are an algebraic type.

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

The Foldable and Traversable instances traverse the real part first.

Note that Complex's instances inherit the deficiencies from the type parameter's. For example, Complex Float's Ord instance has similar problems to Float's.

Constructors

!a :+ !a infix 6

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

Instances
Monad Complex

Since: base-4.9.0.0

Instance details

Defined in Data.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

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Applicative Complex

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

liftA2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Foldable Complex

Since: base-4.9.0.0

Instance details

Defined in Data.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

Since: base-4.9.0.0

Instance details

Defined in Data.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) #

Traversable1 Complex 
Instance details

Defined in Data.Semigroup.Traversable.Class

Methods

traverse1 :: Apply f => (a -> f b) -> Complex a -> f (Complex b) #

sequence1 :: Apply f => Complex (f b) -> f (Complex b) #

Representable Complex 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Complex :: Type #

Methods

tabulate :: (Rep Complex -> a) -> Complex a #

index :: Complex a -> Rep Complex -> a #

Affine Complex 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Complex :: Type -> Type #

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 #

Hashable1 Complex 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Complex a -> Int #

Complicated Complex 
Instance details

Defined in Linear.Quaternion

Methods

_e :: Lens' (Complex a) a #

_i :: Lens' (Complex a) a #

Finite Complex 
Instance details

Defined in Linear.V

Associated Types

type Size Complex :: Nat #

Methods

toV :: Complex a -> V (Size Complex) a #

fromV :: V (Size Complex) a -> Complex a #

Unbox a => Vector Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Eq a => Eq (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

(==) :: Complex a -> Complex a -> Bool #

(/=) :: Complex a -> Complex a -> Bool #

RealFloat a => Floating (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

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)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

(/) :: Complex a -> Complex a -> Complex a #

recip :: Complex a -> Complex a #

fromRational :: Rational -> Complex a #

Data a => Data (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

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)

Since: base-2.1

Instance details

Defined in Data.Complex

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)

Since: base-2.1

Instance details

Defined in Data.Complex

Show a => Show (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Complex a #

Storable a => Storable (Complex a)

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

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

Defined in Control.DeepSeq

Methods

rnf :: Complex a -> () #

Hashable a => Hashable (Complex a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Complex a -> Int #

hash :: Complex a -> Int #

Unbox a => Unbox (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Num e, Elt e) => Elt (Complex e) Source # 
Instance details

Defined in Graphics.Image.Interface.Repa.Generic

Methods

touch :: Complex e -> IO () #

zero :: Complex e #

one :: Complex e #

(Num e, Elevator e, RealFloat e) => Elevator (Complex e) Source #

Discards imaginary part and changes precision of real part.

Instance details

Defined in Graphics.Image.Interface.Elevator

Generic1 Complex 
Instance details

Defined in Data.Complex

Associated Types

type Rep1 Complex :: k -> Type #

Methods

from1 :: Complex a -> Rep1 Complex a #

to1 :: Rep1 Complex a -> Complex a #

Each (Complex a) (Complex b) a b
each :: (RealFloat a, RealFloat b) => Traversal (Complex a) (Complex b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (Complex a) (Complex b) a b #

ComplexWritable format arr cs e => Writable (Image arr cs (Complex e)) format Source #

Writing Complex images: places real part on the left side of imaginary part.

Instance details

Defined in Graphics.Image.IO.Base

Methods

encode :: format -> [SaveOption format] -> Image arr cs (Complex e) -> ByteString Source #

type Rep Complex 
Instance details

Defined in Data.Functor.Rep

type Diff Complex 
Instance details

Defined in Linear.Affine

type Size Complex 
Instance details

Defined in Linear.V

type Size Complex = 2
newtype MVector s (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Complex a) = MV_Complex (MVector s (a, a))
type Rep (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

type Index (Complex a) 
Instance details

Defined in Control.Lens.At

type Index (Complex a) = Int
newtype Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Complex a) = V_Complex (Vector (a, a))
type Rep1 Complex

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

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

X

squashWith :: (Array arr cs e, Array arr X b) => (b -> e -> b) -> b -> Image arr cs e -> Image arr X b Source #

Apply a left fold to each of the pixels in the image.

squashWith2 :: (Array arr cs e, Array arr X b) => (b -> e -> e -> b) -> b -> Image arr cs e -> Image arr cs e -> Image arr X b Source #

Combination of zipWith and simultanious left fold on two pixels at the same time.

toPixelsX :: ColorSpace cs e => Pixel cs e -> [Pixel X e] Source #

Separate a Pixel into a list of components with X pixels containing every component from the pixel.

>>> toPixelsX (PixelRGB 4 5 6)
[<X:(4)>,<X:(5)>,<X:(6)>]

fromPixelsX :: ColorSpace cs e => [(cs, Pixel X e)] -> Pixel cs e Source #

Combine a list of X pixels into a Pixel with a specified channel order. Not the most efficient way to construct a pixel, but might prove useful to someone.

>>> fromPixelsX [(RedRGB, 3), (BlueRGB, 5), (GreenRGB, 4)]
<RGB:(3.0|4.0|5.0)>
>>> fromPixelsX $ zip (enumFrom RedRGB) (toPixelsX $ PixelRGB 4 5 6)
<RGB:(4.0|5.0|6.0)>

toImagesX :: (Array arr cs e, Array arr X e) => Image arr cs e -> [Image arr X e] Source #

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

>>> frog <- readImageRGB "images/frog.jpg"
>>> let [frog_red, frog_green, frog_blue] = toImagesX 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

fromImagesX :: (Array arr X e, Array arr cs e) => [(cs, Image arr X e)] -> Image arr cs e Source #

Combine a list of images with X 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" $ fromImagesX [(RedRGB, frog_red), (BlueRGB, frog_green), (GreenRGB, frog_blue)]

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

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

ColorSpace

Operations on Pixels

eqTolPx :: (ColorSpace cs e, Ord e) => e -> Pixel cs e -> Pixel cs e -> Bool Source #

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

Luma

data Y Source #

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

Constructors

LumaY 
Instances
Bounded Y Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

minBound :: Y #

maxBound :: Y #

Enum Y Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Show Y Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

showsPrec :: Int -> Y -> ShowS #

show :: Y -> String #

showList :: [Y] -> ShowS #

ChannelColour Y Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Associated Types

type Components Y e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel Y e -> Pixel Y e -> b 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 #

ToYCbCr Y e => ToYCbCrA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK Y e => ToCMYKA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI Y e => ToHSIA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB Y e => ToRGBA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY Y e => ToYA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Methods

toPixelY :: Pixel Y e -> Pixel Y Double Source #

Convertible Y Double Source # 
Instance details

Defined in Graphics.Image.IO.Base

Methods

convert :: (ToYA cs' e', ToRGBA cs' e', Array arr cs' e', Array arr Y Double) => Image arr cs' e' -> Image arr Y Double Source #

Monad (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Functor (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Applicative (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

pure :: a -> Pixel Y a #

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

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

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

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

Foldable (Pixel Y) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Readable [Image VS Y Double] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS Y Double] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS Y Word8] (Seq PGM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable [Image VS Y Word16] (Seq PGM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Eq e => Eq (Pixel Y e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

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

Defined in Graphics.Image.ColorSpace.Y

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

show :: Pixel Y e -> String #

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

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

Defined in Graphics.Image.ColorSpace.Y

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) JPG Source #

Image is converted YCbCr color space prior to encoding.

Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Double) PGM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Double) PBM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Double) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) PGM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word16) PGM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

newtype Pixel Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

newtype Pixel Y e = PixelY e
type Components Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

type Components Y e = e

data YA Source #

Luma with Alpha channel.

Constructors

LumaYA

Luma

AlphaYA

Alpha channel

Instances
Bounded YA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

minBound :: YA #

maxBound :: YA #

Enum YA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Show YA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

showsPrec :: Int -> YA -> ShowS #

show :: YA -> String #

showList :: [YA] -> ShowS #

ChannelColour YA Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => AlphaSpace YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Associated Types

type Opaque YA :: Type 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 => ColorSpace YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Associated Types

type Components YA e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel YA e -> Pixel YA e -> b 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 => ToYCbCrA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Convertible YA Double Source # 
Instance details

Defined in Graphics.Image.IO.Base

Methods

convert :: (ToYA cs' e', ToRGBA cs' e', Array arr cs' e', Array arr YA Double) => Image arr cs' e' -> Image arr YA Double Source #

Functor (Pixel YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Applicative (Pixel YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

pure :: a -> Pixel YA a #

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

liftA2 :: (a -> b -> c) -> Pixel YA a -> Pixel YA b -> Pixel YA c #

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

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

Foldable (Pixel YA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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 #

Readable [Image VS YA Double] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS YA Double] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Eq e => Eq (Pixel YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

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

Show e => Show (Pixel YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

Methods

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

show :: Pixel YA e -> String #

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

Storable e => Storable (Pixel YA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) JPG Source #

Image is converted YCbCr color space prior to encoding.

Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS YA Double) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

type Opaque YA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

type Opaque YA = Y
data Pixel YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

data Pixel YA e = PixelYA !e !e
type Components YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Y

type Components YA e = (e, e)

class ColorSpace cs e => ToY cs e Source #

Conversion to Luma color space.

Minimal complete definition

toPixelY

Instances
Elevator e => ToY YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Methods

toPixelY :: Pixel Y e -> Pixel Y Double Source #

Elevator e => ToY RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY RGB e Source #

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

Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Methods

toPixelY :: Pixel X e -> Pixel Y Double Source #

class ToY cs e => ToYA cs e Source #

Conversion to Luma from another color space.

Instances
Elevator e => ToYA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY YCbCr e => ToYA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY Y e => ToYA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY RGB e => ToYA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY HSI e => ToYA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY CMYK e => ToYA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

RGB

data RGB Source #

Red, Green and Blue color space.

Constructors

RedRGB 
GreenRGB 
BlueRGB 
Instances
Bounded RGB Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

minBound :: RGB #

maxBound :: RGB #

Enum RGB Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Show RGB Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

showsPrec :: Int -> RGB -> ShowS #

show :: RGB -> String #

showList :: [RGB] -> ShowS #

ChannelColour RGB Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Associated Types

type Components RGB e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel RGB e -> Pixel RGB e -> b 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 #

ToYCbCr RGB e => ToYCbCrA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK RGB e => ToCMYKA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI RGB e => ToHSIA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB RGB e => ToRGBA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY RGB e => ToYA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY RGB e Source #

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

Instance details

Defined in Graphics.Image.ColorSpace

Convertible RGB Double Source # 
Instance details

Defined in Graphics.Image.IO.Base

Methods

convert :: (ToYA cs' e', ToRGBA cs' e', Array arr cs' e', Array arr RGB Double) => Image arr cs' e' -> Image arr RGB Double Source #

Functor (Pixel RGB) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Applicative (Pixel RGB) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

pure :: a -> Pixel RGB a #

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

liftA2 :: (a -> b -> c) -> Pixel RGB a -> Pixel RGB b -> Pixel RGB c #

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

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

Foldable (Pixel RGB) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Writable [(GifDelay, Image VS RGB Double)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable [(GifDelay, Image VS RGB Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGB Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Double] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Word8] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable [(GifDelay, Image VS RGB Double)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable [(GifDelay, Image VS RGB Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGB Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Double] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Word8] (Seq PPM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable [Image VS RGB Word8] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Word16] (Seq PPM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Eq e => Eq (Pixel RGB e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Show e => Show (Pixel RGB e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

show :: Pixel RGB e -> String #

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

Storable e => Storable (Pixel RGB e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) JPG Source #

Image is converted YCbCr color space prior to encoding.

Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Float) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGB Double) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Float) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGB Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word16) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGB Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

data Pixel RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

data Pixel RGB e = PixelRGB !e !e !e
type Components RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

type Components RGB e = (e, e, e)

data RGBA Source #

Red, Green and Blue color space with Alpha channel.

Instances
Bounded RGBA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Enum RGBA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Show RGBA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

showsPrec :: Int -> RGBA -> ShowS #

show :: RGBA -> String #

showList :: [RGBA] -> ShowS #

ChannelColour RGBA Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => AlphaSpace RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Associated Types

type Opaque RGBA :: Type Source #

Elevator e => ColorSpace RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Associated Types

type Components RGBA e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel RGBA e -> Pixel RGBA e -> b 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 => ToYCbCrA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Convertible RGBA Double Source # 
Instance details

Defined in Graphics.Image.IO.Base

Methods

convert :: (ToYA cs' e', ToRGBA cs' e', Array arr cs' e', Array arr RGBA Double) => Image arr cs' e' -> Image arr RGBA Double Source #

Functor (Pixel RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Applicative (Pixel RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

pure :: a -> Pixel RGBA a #

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

liftA2 :: (a -> b -> c) -> Pixel RGBA a -> Pixel RGBA b -> Pixel RGBA c #

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

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

Foldable (Pixel RGBA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 #

Readable [(GifDelay, Image VS RGBA Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGBA Double] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGBA Word8] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable [(GifDelay, Image VS RGBA Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGBA Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGBA Double] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGBA Word8] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Eq e => Eq (Pixel RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

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

Show e => Show (Pixel RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

Methods

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

show :: Pixel RGBA e -> String #

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

Storable e => Storable (Pixel RGBA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) JPG Source #

Image is converted YCbCr color space prior to encoding.

Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGBA Double) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) HDR Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Double) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

type Opaque RGBA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

type Opaque RGBA = RGB
data Pixel RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

data Pixel RGBA e = PixelRGBA !e !e !e !e
type Components RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.RGB

type Components RGBA e = (e, e, e, e)

class ColorSpace cs e => ToRGB cs e Source #

Conversion to RGB color space.

Minimal complete definition

toPixelRGB

Instances
Elevator e => ToRGB YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

class ToRGB cs e => ToRGBA cs e Source #

Conversion to RGBA from another color space with Alpha channel.

Instances
Elevator e => ToRGBA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB YCbCr e => ToRGBA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB Y e => ToRGBA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB RGB e => ToRGBA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB HSI e => ToRGBA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB CMYK e => ToRGBA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGBA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

HSI

data HSI Source #

Hue, Saturation and Intensity color space.

Constructors

HueHSI

Hue

SatHSI

Saturation

IntHSI

Intensity

Instances
Bounded HSI Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

minBound :: HSI #

maxBound :: HSI #

Enum HSI Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Show HSI Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

showsPrec :: Int -> HSI -> ShowS #

show :: HSI -> String #

showList :: [HSI] -> ShowS #

ChannelColour HSI Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Associated Types

type Components HSI e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel HSI e -> Pixel HSI e -> b 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 #

ToYCbCr HSI e => ToYCbCrA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK HSI e => ToCMYKA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI HSI e => ToHSIA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB HSI e => ToRGBA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY HSI e => ToYA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel HSI) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Applicative (Pixel HSI) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

pure :: a -> Pixel HSI a #

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

liftA2 :: (a -> b -> c) -> Pixel HSI a -> Pixel HSI b -> Pixel HSI c #

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

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

Foldable (Pixel HSI) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Eq e => Eq (Pixel HSI e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Show e => Show (Pixel HSI e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

show :: Pixel HSI e -> String #

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

Storable e => Storable (Pixel HSI e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

data Pixel HSI e = PixelHSI !e !e !e
type Components HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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
Bounded HSIA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Enum HSIA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Show HSIA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

showsPrec :: Int -> HSIA -> ShowS #

show :: HSIA -> String #

showList :: [HSIA] -> ShowS #

ChannelColour HSIA Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => AlphaSpace HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Associated Types

type Opaque HSIA :: Type Source #

Elevator e => ColorSpace HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Associated Types

type Components HSIA e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel HSIA e -> Pixel HSIA e -> b 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 => ToYCbCrA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Applicative (Pixel HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

pure :: a -> Pixel HSIA a #

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

liftA2 :: (a -> b -> c) -> Pixel HSIA a -> Pixel HSIA b -> Pixel HSIA c #

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

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

Foldable (Pixel HSIA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

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

Show e => Show (Pixel HSIA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

Methods

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

show :: Pixel HSIA e -> String #

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

Storable e => Storable (Pixel HSIA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

type Opaque HSIA = HSI
data Pixel HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

data Pixel HSIA e = PixelHSIA !e !e !e !e
type Components HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.HSI

type Components HSIA e = (e, e, e, e)

class ColorSpace cs e => ToHSI cs e Source #

Conversion to HSI color space.

Minimal complete definition

toPixelHSI

Instances
Elevator e => ToHSI YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

class ToHSI cs e => ToHSIA cs e Source #

Conversion to HSIA from another color space with Alpha channel.

Instances
Elevator e => ToHSIA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI YCbCr e => ToHSIA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI Y e => ToHSIA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI RGB e => ToHSIA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI HSI e => ToHSIA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI CMYK e => ToHSIA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

CMYK

data CMYK Source #

Cyan, Magenta, Yellow and Black color space.

Constructors

CyanCMYK

Cyan

MagCMYK

Magenta

YelCMYK

Yellow

KeyCMYK

Key (Black)

Instances
Bounded CMYK Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Enum CMYK Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Show CMYK Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

showsPrec :: Int -> CMYK -> ShowS #

show :: CMYK -> String #

showList :: [CMYK] -> ShowS #

ChannelColour CMYK Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Associated Types

type Components CMYK e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel CMYK e -> Pixel CMYK e -> b 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 #

ToYCbCr CMYK e => ToYCbCrA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK CMYK e => ToCMYKA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI CMYK e => ToHSIA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB CMYK e => ToRGBA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY CMYK e => ToYA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel CMYK) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Applicative (Pixel CMYK) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

pure :: a -> Pixel CMYK a #

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

liftA2 :: (a -> b -> c) -> Pixel CMYK a -> Pixel CMYK b -> Pixel CMYK c #

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

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

Foldable (Pixel CMYK) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Eq e => Eq (Pixel CMYK e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Show e => Show (Pixel CMYK e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

show :: Pixel CMYK e -> String #

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

Storable e => Storable (Pixel CMYK e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

data Pixel CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

data Pixel CMYK e = PixelCMYK !e !e !e !e
type Components CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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
Bounded CMYKA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Enum CMYKA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Eq CMYKA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Show CMYKA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

showsPrec :: Int -> CMYKA -> ShowS #

show :: CMYKA -> String #

showList :: [CMYKA] -> ShowS #

ChannelColour CMYKA Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => AlphaSpace CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Associated Types

type Opaque CMYKA :: Type Source #

Elevator e => ColorSpace CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Associated Types

type Components CMYKA e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel CMYKA e -> Pixel CMYKA e -> b 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 => ToYCbCrA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Applicative (Pixel CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

pure :: a -> Pixel CMYKA a #

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

liftA2 :: (a -> b -> c) -> Pixel CMYKA a -> Pixel CMYKA b -> Pixel CMYKA c #

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

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

Foldable (Pixel CMYKA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

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

Show e => Show (Pixel CMYKA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

Methods

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

show :: Pixel CMYKA e -> String #

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

Storable e => Storable (Pixel CMYKA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

data Pixel CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

data Pixel CMYKA e = PixelCMYKA !e !e !e !e !e
type Components CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.CMYK

type Components CMYKA e = (e, e, e, e, e)

class ColorSpace cs e => ToCMYK cs e Source #

Conversion to CMYK color space.

Minimal complete definition

toPixelCMYK

Instances
Elevator e => ToCMYK YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

class ToCMYK cs e => ToCMYKA cs e Source #

Conversion to CMYKA.

Instances
Elevator e => ToCMYKA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK YCbCr e => ToCMYKA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK Y e => ToCMYKA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK RGB e => ToCMYKA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK HSI e => ToCMYKA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK CMYK e => ToCMYKA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

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
Bounded YCbCr Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Enum YCbCr Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Eq YCbCr Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Show YCbCr Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

showsPrec :: Int -> YCbCr -> ShowS #

show :: YCbCr -> String #

showList :: [YCbCr] -> ShowS #

ChannelColour YCbCr Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Associated Types

type Components YCbCr e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel YCbCr e -> Pixel YCbCr e -> b 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 #

ToYCbCr YCbCr e => ToYCbCrA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToCMYK YCbCr e => ToCMYKA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToHSI YCbCr e => ToHSIA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB YCbCr e => ToRGBA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToY YCbCr e => ToYA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel YCbCr) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Applicative (Pixel YCbCr) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

pure :: a -> Pixel YCbCr a #

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

liftA2 :: (a -> b -> c) -> Pixel YCbCr a -> Pixel YCbCr b -> Pixel YCbCr c #

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

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

Foldable (Pixel YCbCr) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.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 #

Eq e => Eq (Pixel YCbCr e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Show e => Show (Pixel YCbCr e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

show :: Pixel YCbCr e -> String #

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

Storable e => Storable (Pixel YCbCr e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YCbCr Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YCbCr Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YCbCr Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

data Pixel YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

data Pixel YCbCr e = PixelYCbCr !e !e !e
type Components YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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
Bounded YCbCrA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Enum YCbCrA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Eq YCbCrA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Show YCbCrA Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

ChannelColour YCbCrA Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => AlphaSpace YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Associated Types

type Opaque YCbCrA :: Type Source #

Elevator e => ColorSpace YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Associated Types

type Components YCbCrA e :: Type Source #

Methods

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

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

promote :: 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 #

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

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

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel YCbCrA e -> Pixel YCbCrA e -> b 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 => ToYCbCrA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYKA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToCMYK YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSIA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToHSI YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGBA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToRGB YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Functor (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Applicative (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

pure :: a -> Pixel YCbCrA a #

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

liftA2 :: (a -> b -> c) -> Pixel YCbCrA a -> Pixel YCbCrA b -> Pixel YCbCrA c #

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

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

Foldable (Pixel YCbCrA) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Methods

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

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

Show e => Show (Pixel YCbCrA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

Storable e => Storable (Pixel YCbCrA e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

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 # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

data Pixel YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

data Pixel YCbCrA e = PixelYCbCrA !e !e !e !e
type Components YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.YCbCr

type Components YCbCrA e = (e, e, e, e)

class ColorSpace cs e => ToYCbCr cs e Source #

Conversion to YCbCr color space.

Minimal complete definition

toPixelYCbCr

Instances
Elevator e => ToYCbCr YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCr CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

class ToYCbCr cs e => ToYCbCrA cs e Source #

Conversion to YCbCrA from another color space with Alpha channel.

Instances
Elevator e => ToYCbCrA YCbCrA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYCbCr YCbCr e => ToYCbCrA YCbCr e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCrA YA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYCbCr Y e => ToYCbCrA Y e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCrA RGBA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYCbCr RGB e => ToYCbCrA RGB e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCrA HSIA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYCbCr HSI e => ToYCbCrA HSI e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToYCbCrA CMYKA e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYCbCr CMYK e => ToYCbCrA CMYK e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

X

data X 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

X 
Instances
Bounded X Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

minBound :: X #

maxBound :: X #

Enum X Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

succ :: X -> X #

pred :: X -> X #

toEnum :: Int -> X #

fromEnum :: X -> Int #

enumFrom :: X -> [X] #

enumFromThen :: X -> X -> [X] #

enumFromTo :: X -> X -> [X] #

enumFromThenTo :: X -> X -> X -> [X] #

Eq X Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

Show X Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

showsPrec :: Int -> X -> ShowS #

show :: X -> String #

showList :: [X] -> ShowS #

ChannelColour X Source # 
Instance details

Defined in Graphics.Image.IO.Histogram

Elevator e => ColorSpace X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Associated Types

type Components X e :: Type Source #

Methods

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

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

promote :: e -> Pixel X e Source #

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

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

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

liftPx :: (e -> e) -> Pixel X e -> Pixel X e Source #

liftPx2 :: (e -> e -> e) -> Pixel X e -> Pixel X e -> Pixel X e Source #

foldlPx2 :: (b -> e -> e -> b) -> b -> Pixel X e -> Pixel X e -> b Source #

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

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

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

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

ToRGBA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToRGB X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

ToYA X Bit Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Elevator e => ToY X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace

Methods

toPixelY :: Pixel X e -> Pixel Y Double Source #

Monad (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

return :: a -> Pixel X a #

fail :: String -> Pixel X a #

Functor (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

Applicative (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

pure :: a -> Pixel X a #

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

liftA2 :: (a -> b -> c) -> Pixel X a -> Pixel X b -> Pixel X c #

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

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

Foldable (Pixel X) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

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

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

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

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

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

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

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

null :: Pixel X a -> Bool #

length :: Pixel X a -> Int #

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

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

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

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

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

Readable [Image VS X Bit] (Seq PBM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Eq e => Eq (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

Ord e => Ord (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

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

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

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

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

max :: Pixel X e -> Pixel X e -> Pixel X e #

min :: Pixel X e -> Pixel X e -> Pixel X e #

Show e => Show (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

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

show :: Pixel X e -> String #

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

Storable e => Storable (Pixel X e) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

Methods

sizeOf :: Pixel X e -> Int #

alignment :: Pixel X e -> Int #

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

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

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

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

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

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

Bits (Pixel X Bit) Source # 
Instance details

Defined in Graphics.Image.ColorSpace.Binary

Writable (Image VS X Bit) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS X Bit) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) PBM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS X Bit) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS X Bit) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

newtype Pixel X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

newtype Pixel X e = PixelX {}
type Components X e Source # 
Instance details

Defined in Graphics.Image.ColorSpace.X

type Components X e = e

Precision

Image

toWord8I :: (Functor (Pixel cs), Array arr cs e, Array arr cs Word8) => Image arr cs e -> Image arr cs Word8 Source #

Change image precision to Word8.

toWord16I :: (Functor (Pixel cs), Array arr cs e, Array arr cs Word16) => Image arr cs e -> Image arr cs Word16 Source #

Change image precision to Word16.

toWord32I :: (Functor (Pixel cs), Array arr cs e, Array arr cs Word32) => Image arr cs e -> Image arr cs Word32 Source #

Change image precision to Word32.

toFloatI :: (Functor (Pixel cs), Array arr cs e, Array arr cs Float) => Image arr cs e -> Image arr cs Float Source #

Change image precision to Float.

toDoubleI :: (Functor (Pixel cs), Array arr cs e, Array arr cs Double) => Image arr cs e -> Image arr cs Double Source #

Change image precision to Double.

Pixel

toWord8Px :: (Functor (Pixel cs), Elevator e) => Pixel cs e -> Pixel cs Word8 Source #

Change pixel precision to Word8.

Componenet

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

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

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

TiffSaveable Pixel8 
Instance details

Defined in Codec.Picture.Tiff

JpgEncodable Pixel8 
Instance details

Defined in Codec.Picture.Jpg

BmpEncodable Pixel8 
Instance details

Defined in Codec.Picture.Bitmap

PngSavable Pixel8 
Instance details

Defined in Codec.Picture.Png.Internal.Export

TgaSaveable Pixel8 
Instance details

Defined in Codec.Picture.Tga

Pixel Pixel8 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PixelBaseComponent Pixel8 :: Type #

LumaPlaneExtractable Pixel8 
Instance details

Defined in Codec.Picture.Types

PackeablePixel Pixel8 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PackedRepresentation Pixel8 :: Type #

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

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

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

Elt Word8 
Instance details

Defined in Data.Array.Repa.Eval.Elt

Methods

touch :: Word8 -> IO () #

zero :: Word8 #

one :: Word8 #

Elevator Word8 Source #

Values between [0, 255]]

Instance details

Defined in Graphics.Image.Interface.Elevator

Unpackable Word8

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

Instance details

Defined in Codec.Picture.Tiff

Associated Types

type StorageType Word8 :: Type

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

TransparentPixel PixelYA8 Pixel8 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 Pixel16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 PixelF 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 PixelYA8 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 PixelRGB8 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 PixelRGB16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 PixelRGBA8 
Instance details

Defined in Codec.Picture.Types

IArray UArray Word8 
Instance details

Defined in Data.Array.Base

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 
Instance details

Defined in Data.Vector.Unboxed.Base

Source B Word8

Read elements from a ByteString.

Instance details

Defined in Data.Array.Repa.Repr.ByteString

Associated Types

data Array B sh Word8 :: Type #

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 
Instance details

Defined in Data.Vector.Unboxed.Base

Decimable Pixel16 Pixel8 
Instance details

Defined in Codec.Picture

Decimable Pixel32 Pixel8 
Instance details

Defined in Codec.Picture

Decimable PixelF Pixel8 
Instance details

Defined in Codec.Picture

Structured B Word8 b 
Instance details

Defined in Data.Array.Repa.Operators.Mapping

Associated Types

type TR B :: Type #

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 #

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Writable [(GifDelay, Image VS RGB Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGBA Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGB Word8)] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGBA Word8] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Word8] GIFA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

MArray (STUArray s) Word8 (ST s) 
Instance details

Defined in Data.Array.Base

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 RGBA Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable [(GifDelay, Image VS RGB Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGBA Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [(GifDelay, Image VS RGB Word8)] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS Y Word8] (Seq PGM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable [Image VS RGBA Word8] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable [Image VS RGB Word8] (Seq PPM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable [Image VS RGB Word8] (Seq GIF) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Read sh => Read (Array B sh Word8) 
Instance details

Defined in Data.Array.Repa.Repr.ByteString

Show sh => Show (Array B sh Word8) 
Instance details

Defined in Data.Array.Repa.Repr.ByteString

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 # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YCbCr Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YCbCr Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) PGM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGB Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) TGA Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) GIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word8) BMP Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word8) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word8) JPG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

type PixelBaseComponent Pixel8 
Instance details

Defined in Codec.Picture.Types

type PackedRepresentation Pixel8 
Instance details

Defined in Codec.Picture.Types

type Unsigned Word8 
Instance details

Defined in Data.Bytes.Signed

type Signed Word8 
Instance details

Defined in Data.Bytes.Signed

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type StorageType Word8 
Instance details

Defined in Codec.Picture.Tiff

type StorageType Word8 = Word8
newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Array B sh Word8 
Instance details

Defined in Data.Array.Repa.Repr.ByteString

data Word16 #

16-bit unsigned integer type

Instances
Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

TiffSaveable Pixel16 
Instance details

Defined in Codec.Picture.Tiff

PngSavable Pixel16 
Instance details

Defined in Codec.Picture.Png.Internal.Export

Pixel Pixel16 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PixelBaseComponent Pixel16 :: Type #

LumaPlaneExtractable Pixel16 
Instance details

Defined in Codec.Picture.Types

PackeablePixel Pixel16 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PackedRepresentation Pixel16 :: Type #

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Random Word16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) #

random :: RandomGen g => g -> (Word16, g) #

randomRs :: RandomGen g => (Word16, Word16) -> g -> [Word16] #

randoms :: RandomGen g => g -> [Word16] #

randomRIO :: (Word16, Word16) -> IO Word16 #

randomIO :: IO Word16 #

Elt Word16 
Instance details

Defined in Data.Array.Repa.Eval.Elt

Methods

touch :: Word16 -> IO () #

zero :: Word16 #

one :: Word16 #

Elevator Word16 Source #

Values between [0, 65535]]

Instance details

Defined in Graphics.Image.Interface.Elevator

Unpackable Word16 
Instance details

Defined in Codec.Picture.Tiff

Associated Types

type StorageType Word16 :: Type

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

TransparentPixel PixelYA16 Pixel16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel8 Pixel16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel16 PixelYA16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel16 PixelRGB16 
Instance details

Defined in Codec.Picture.Types

ColorConvertible Pixel16 PixelRGBA16 
Instance details

Defined in Codec.Picture.Types

IArray UArray Word16 
Instance details

Defined in Data.Array.Base

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 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Decimable Pixel16 Pixel8 
Instance details

Defined in Codec.Picture

Decimable Pixel32 Pixel16 
Instance details

Defined in Codec.Picture

Decimable PixelF Pixel16 
Instance details

Defined in Codec.Picture

MArray (STUArray s) Word16 (ST s) 
Instance details

Defined in Data.Array.Base

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 Y Word16] (Seq PGM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable [Image VS RGB Word16] (Seq PPM) Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Writable (Image VS YA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS YA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS Y Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGBA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS RGB Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Writable (Image VS CMYK Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS YA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word16) PGM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS Y Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS Y Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGBA Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word16) PPM Source # 
Instance details

Defined in Graphics.Image.IO.Formats.Netpbm

Readable (Image VS RGB Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS RGB Word16) PNG Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

Readable (Image VS CMYK Word16) TIF Source # 
Instance details

Defined in Graphics.Image.IO.Formats.JuicyPixels

type PixelBaseComponent Pixel16 
Instance details

Defined in Codec.Picture.Types

type PackedRepresentation Pixel16 
Instance details

Defined in Codec.Picture.Types

type Unsigned Word16 
Instance details

Defined in Data.Bytes.Signed

type Signed Word16 
Instance details

Defined in Data.Bytes.Signed

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

type StorageType Word16 
Instance details

Defined in Codec.Picture.Tiff

type StorageType Word16 = Word16
newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

TiffSaveable Pixel32 
Instance details

Defined in Codec.Picture.Tiff

Pixel Pixel32 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PixelBaseComponent Pixel32 :: Type #

LumaPlaneExtractable Pixel32 
Instance details

Defined in Codec.Picture.Types

PackeablePixel Pixel32 
Instance details

Defined in Codec.Picture.Types

Associated Types

type PackedRepresentation Pixel32 :: Type #

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Random Word32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) #

random :: RandomGen g => g -> (Word32, g) #

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32] #

randoms :: RandomGen g => g -> [Word32] #

randomRIO :: (Word32, Word32) -> IO Word32 #

randomIO :: IO Word32 #

Elt Word32 
Instance details

Defined in Data.Array.Repa.Eval.Elt

Methods

touch :: Word32 -> IO () #

zero :: Word32 #

one :: Word32 #

Elevator Word32 Source #

Values between [0, 4294967295]

Instance details

Defined in Graphics.Image.Interface.Elevator

Unpackable Word32 
Instance details

Defined in Codec.Picture.Tiff

Associated Types

type StorageType Word32 :: Type

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

IArray UArray Word32 
Instance details

Defined in Data.Array.Base

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 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Decimable Pixel32 Pixel8 
Instance details

Defined in Codec.Picture

Decimable Pixel32 Pixel16 
Instance details

Defined in Codec.Picture

MArray (STUArray s) Word32 (ST s) 
Instance details

Defined in Data.Array.Base

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 PixelBaseComponent Pixel32 
Instance details

Defined in Codec.Picture.Types

type PackedRepresentation Pixel32 
Instance details

Defined in Codec.Picture.Types

type Unsigned Word32 
Instance details

Defined in Data.Bytes.Signed

type Signed Word32 
Instance details

Defined in Data.Bytes.Signed

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

type StorageType Word32 
Instance details

Defined in Codec.Picture.Tiff

type StorageType Word32 = Word32
newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word64 #

64-bit unsigned integer type

Instances
Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Random Word64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) #

random :: RandomGen g => g -> (Word64, g) #

randomRs :: RandomGen g => (Word64, Word64) -> g -> [Word64] #

randoms :: RandomGen g => g -> [Word64] #

randomRIO :: (Word64, Word64) -> IO Word64 #

randomIO :: IO Word64 #

Elt Word64 
Instance details

Defined in Data.Array.Repa.Eval.Elt

Methods

touch :: Word64 -> IO () #

zero :: Word64 #

one :: Word64 #

Elevator Word64 Source #

Values between [0, 18446744073709551615]

Instance details

Defined in Graphics.Image.Interface.Elevator

IArray UArray Word64 
Instance details

Defined in Data.Array.Base

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 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MArray (STUArray s) Word64 (ST s) 
Instance details

Defined in Data.Array.Base

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 
Instance details

Defined in Data.Bytes.Signed

type Signed Word64 
Instance details

Defined in Data.Bytes.Signed

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base