massiv-io-0.1.6.0: Import/export of Image files into massiv Arrays

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

Graphics.ColorSpace.RGB

Description

 
Synopsis

Documentation

data RGB Source #

Red, Green and Blue color space.

Constructors

RedRGB 
GreenRGB 
BlueRGB 
Instances
Bounded RGB Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

Methods

minBound :: RGB #

maxBound :: RGB #

Enum RGB Source # 
Instance details

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

Methods

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

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

Show RGB Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

Methods

showsPrec :: Int -> RGB -> ShowS #

show :: RGB -> String #

showList :: [RGB] -> ShowS #

Elevator e => ColorSpace RGB e Source # 
Instance details

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

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

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 #

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

Defined in Graphics.ColorSpace

Elevator e => ToYCbCr RGB e Source # 
Instance details

Defined in Graphics.ColorSpace

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

Defined in Graphics.ColorSpace

Elevator e => ToCMYK RGB e Source # 
Instance details

Defined in Graphics.ColorSpace

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

Defined in Graphics.ColorSpace

Elevator e => ToHSI RGB e Source # 
Instance details

Defined in Graphics.ColorSpace

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

Defined in Graphics.ColorSpace

Elevator e => ToRGB RGB e Source # 
Instance details

Defined in Graphics.ColorSpace

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

Defined in Graphics.ColorSpace

Elevator e => ToY RGB e Source #

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

Instance details

Defined in Graphics.ColorSpace

Functor (Pixel RGB) Source # 
Instance details

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

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

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

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

max :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

min :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

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

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

data Pixel RGB e Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

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

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

Enum RGBA Source # 
Instance details

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

Methods

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

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

Show RGBA Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

Methods

showsPrec :: Int -> RGBA -> ShowS #

show :: RGBA -> String #

showList :: [RGBA] -> ShowS #

Elevator e => AlphaSpace RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

Associated Types

type Opaque RGBA :: Type Source #

Elevator e => ColorSpace RGBA e Source # 
Instance details

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

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

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 #

Elevator e => ToYCbCrA RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToYCbCr RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToCMYKA RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToCMYK RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToHSIA RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToHSI RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToRGBA RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToRGB RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToYA RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Elevator e => ToY RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace

Functor (Pixel RGBA) Source # 
Instance details

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

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

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

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

max :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

min :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

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

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

type Opaque RGBA Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

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

Defined in Graphics.ColorSpace.RGB

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

Defined in Graphics.ColorSpace.RGB

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

data family Pixel cs e :: * Source #

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

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

Defined in Graphics.ColorSpace.Internal

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.ColorSpace.Internal

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

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable TIF (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: TIF -> WriteOptions TIF -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable TGA (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: TGA -> WriteOptions TGA -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable JPG (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: JPG -> WriteOptions JPG -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable HDR (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: HDR -> WriteOptions HDR -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable GIF (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: GIF -> WriteOptions GIF -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable PNG (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: PNG -> WriteOptions PNG -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable BMP (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: BMP -> WriteOptions BMP -> Image r cs e -> ByteString Source #

ColorSpace cs e => Readable TIF (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: TIF -> ReadOptions TIF -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable TGA (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: TGA -> ReadOptions TGA -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable JPG (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: JPG -> ReadOptions JPG -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable HDR (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: HDR -> ReadOptions HDR -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable GIF (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: GIF -> ReadOptions GIF -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable PNG (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: PNG -> ReadOptions PNG -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable BMP (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: BMP -> ReadOptions BMP -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable PPM (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: PPM -> ReadOptions PPM -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable PGM (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: PGM -> ReadOptions PGM -> ByteString -> Image S cs e Source #

ColorSpace cs e => Readable PBM (Image S cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: PBM -> ReadOptions PBM -> ByteString -> Image S cs e Source #

Monad (Pixel X) Source # 
Instance details

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

Monad (Pixel Y) Source # 
Instance details

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

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

Methods

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

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

Functor (Pixel RGBA) Source # 
Instance details

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

Methods

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

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

Functor (Pixel X) Source # 
Instance details

Defined in Graphics.ColorSpace.X

Methods

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

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

Functor (Pixel YA) Source # 
Instance details

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

Methods

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

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

Functor (Pixel YCbCrA) Source # 
Instance details

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

Methods

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

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

Applicative (Pixel HSIA) Source # 
Instance details

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

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

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

Applicative (Pixel YA) Source # 
Instance details

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

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

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

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

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

Foldable (Pixel YA) Source # 
Instance details

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

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

FileFormat (Decode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

Associated Types

type ReadOptions (Decode (Image r cs e)) :: Type Source #

type WriteOptions (Decode (Image r cs e)) :: Type Source #

Methods

ext :: Decode (Image r cs e) -> String Source #

exts :: Decode (Image r cs e) -> [String] Source #

isFormat :: String -> Decode (Image r cs e) -> Bool Source #

FileFormat (Encode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

Associated Types

type ReadOptions (Encode (Image r cs e)) :: Type Source #

type WriteOptions (Encode (Image r cs e)) :: Type Source #

Methods

ext :: Encode (Image r cs e) -> String Source #

exts :: Encode (Image r cs e) -> [String] Source #

isFormat :: String -> Encode (Image r cs e) -> Bool Source #

(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto TIF) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto TIF -> WriteOptions (Auto TIF) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto TGA) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto TGA -> WriteOptions (Auto TGA) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToYCbCr cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto JPG) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto JPG -> WriteOptions (Auto JPG) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToRGB cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto HDR) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto HDR -> WriteOptions (Auto HDR) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToY cs e, ToRGB cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto GIF) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto GIF -> WriteOptions (Auto GIF) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToYA cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto PNG) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto PNG -> WriteOptions (Auto PNG) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto BMP) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

encode :: Auto BMP -> WriteOptions (Auto BMP) -> Image r cs e -> ByteString Source #

(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable (Sequence GIF) (Array B Ix1 (GifDelay, Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Writable (Encode (Image r cs e)) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

Methods

encode :: Encode (Image r cs e) -> WriteOptions (Encode (Image r cs e)) -> Image r cs e -> ByteString Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto TIF) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto TIF -> ReadOptions (Auto TIF) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto TGA) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto TGA -> ReadOptions (Auto TGA) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto JPG) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto JPG -> ReadOptions (Auto JPG) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto HDR) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto HDR -> ReadOptions (Auto HDR) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto GIF) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto GIF -> ReadOptions (Auto GIF) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PNG) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto PNG -> ReadOptions (Auto PNG) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto BMP) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

Methods

decode :: Auto BMP -> ReadOptions (Auto BMP) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PPM) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: Auto PPM -> ReadOptions (Auto PPM) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PGM) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: Auto PGM -> ReadOptions (Auto PGM) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PBM) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Methods

decode :: Auto PBM -> ReadOptions (Auto PBM) -> ByteString -> Image r cs e Source #

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto GIF)) (Array B Ix1 (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PPM)) (Array B Ix1 (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PGM)) (Array B Ix1 (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PBM)) (Array B Ix1 (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

ColorSpace cs e => Readable (Sequence GIF) (Array B Ix1 (GifDelay, Image S cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

ColorSpace cs e => Readable (Sequence GIF) (Array B Ix1 (Image S cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.JuicyPixels

ColorSpace cs e => Readable (Sequence PPM) (Array B Ix1 (Image S cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

ColorSpace cs e => Readable (Sequence PGM) (Array B Ix1 (Image S cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

ColorSpace cs e => Readable (Sequence PBM) (Array B Ix1 (Image S cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image.Netpbm

Readable (Decode (Image r cs e)) (Image r cs e) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

Methods

decode :: Decode (Image r cs e) -> ReadOptions (Decode (Image r cs e)) -> ByteString -> Image r cs e Source #

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

Defined in Graphics.ColorSpace.Internal

Methods

minBound :: Pixel cs e #

maxBound :: Pixel cs e #

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

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

Methods

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

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

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

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

Methods

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

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

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

Defined in Graphics.ColorSpace.X

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

Defined in Graphics.ColorSpace.Internal

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.ColorSpace.Internal

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.ColorSpace.Internal

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

Defined in Graphics.ColorSpace.HSI

Methods

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

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

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

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

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

max :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

min :: Pixel HSIA e -> Pixel HSIA e -> Pixel HSIA e #

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

Defined in Graphics.ColorSpace.HSI

Methods

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

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

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

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

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

max :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

min :: Pixel HSI e -> Pixel HSI e -> Pixel HSI e #

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

Defined in Graphics.ColorSpace.CMYK

Methods

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

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

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

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

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

max :: Pixel CMYKA e -> Pixel CMYKA e -> Pixel CMYKA e #

min :: Pixel CMYKA e -> Pixel CMYKA e -> Pixel CMYKA e #

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

Defined in Graphics.ColorSpace.CMYK

Methods

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

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

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

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

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

max :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

min :: Pixel CMYK e -> Pixel CMYK e -> Pixel CMYK e #

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

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

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

max :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

min :: Pixel RGBA e -> Pixel RGBA e -> Pixel RGBA e #

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

Defined in Graphics.ColorSpace.RGB

Methods

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

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

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

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

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

max :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

min :: Pixel RGB e -> Pixel RGB e -> Pixel RGB e #

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

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

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

Defined in Graphics.ColorSpace.Y

Methods

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

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

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

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

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

max :: Pixel YA e -> Pixel YA e -> Pixel YA e #

min :: Pixel YA e -> Pixel YA e -> Pixel YA e #

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

Defined in Graphics.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 YCbCrA e) Source # 
Instance details

Defined in Graphics.ColorSpace.YCbCr

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

Defined in Graphics.ColorSpace.YCbCr

Methods

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

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

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

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

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

max :: Pixel YCbCr e -> Pixel YCbCr e -> Pixel YCbCr e #

min :: Pixel YCbCr e -> Pixel YCbCr e -> Pixel YCbCr e #

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

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

Methods

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

show :: Pixel CMYK e -> String #

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

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

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

Methods

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

show :: Pixel RGB e -> String #

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

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

Defined in Graphics.ColorSpace.X

Methods

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

show :: Pixel X e -> String #

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

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

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

Methods

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

show :: Pixel Y e -> String #

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

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

Defined in Graphics.ColorSpace.YCbCr

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

Defined in Graphics.ColorSpace.YCbCr

Methods

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

show :: Pixel YCbCr e -> String #

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

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

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

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

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

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

Defined in Graphics.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.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 YCbCrA e) Source # 
Instance details

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

Bits (Pixel X Bit) Source # 
Instance details

Defined in Graphics.ColorSpace.Binary

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

Defined in Graphics.ColorSpace.Internal

Methods

def :: Pixel cs e #

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

Defined in Graphics.ColorSpace.Internal

Methods

rnf :: Pixel cs e -> () #

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

Unboxing of a Pixel.

Instance details

Defined in Graphics.ColorSpace.Internal

data Pixel HSIA e Source # 
Instance details

Defined in Graphics.ColorSpace.HSI

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

Defined in Graphics.ColorSpace.HSI

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

Defined in Graphics.ColorSpace.CMYK

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

Defined in Graphics.ColorSpace.CMYK

data Pixel CMYK e = PixelCMYK !e !e !e !e
data Pixel RGBA e Source # 
Instance details

Defined in Graphics.ColorSpace.RGB

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

Defined in Graphics.ColorSpace.RGB

data Pixel RGB e = PixelRGB !e !e !e
newtype Pixel X e Source # 
Instance details

Defined in Graphics.ColorSpace.X

newtype Pixel X e = PixelX {}
data Pixel YA e Source # 
Instance details

Defined in Graphics.ColorSpace.Y

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

Defined in Graphics.ColorSpace.Y

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

Defined in Graphics.ColorSpace.YCbCr

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

Defined in Graphics.ColorSpace.YCbCr

data Pixel YCbCr e = PixelYCbCr !e !e !e
newtype MVector s (Pixel cs e) Source # 
Instance details

Defined in Graphics.ColorSpace.Internal

newtype MVector s (Pixel cs e) = MV_Pixel (MVector s (Components cs e))
type ReadOptions (Decode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

type ReadOptions (Decode (Image r cs e)) = ()
type ReadOptions (Encode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

type ReadOptions (Encode (Image r cs e)) = ()
type WriteOptions (Decode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

type WriteOptions (Decode (Image r cs e)) = ()
type WriteOptions (Encode (Image r cs e)) Source # 
Instance details

Defined in Data.Massiv.Array.IO.Image

type WriteOptions (Encode (Image r cs e)) = ()
newtype Vector (Pixel cs e) Source # 
Instance details

Defined in Graphics.ColorSpace.Internal

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