Color-0.2.0: Color spaces and conversions between them

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

Graphics.Color.Space.RGB.Derived.SRGB

Description

 
Synopsis

Documentation

data SRGB (i :: k) (l :: Linearity) Source #

The most common sRGB color space with an arbitrary illuminant

Instances
Illuminant i => RedGreenBlue (SRGB i) (i :: k) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

gamut :: RealFloat e => Gamut (SRGB i) i e Source #

ecctf :: (RealFloat a, Elevator a) => Color (SRGB i Linear) a -> Color (SRGB i NonLinear) a Source #

dcctf :: (RealFloat a, Elevator a) => Color (SRGB i NonLinear) a -> Color (SRGB i Linear) a Source #

npm :: (ColorSpace (SRGB i Linear) i a, RealFloat a) => NPM (SRGB i) a Source #

inpm :: (ColorSpace (SRGB i Linear) i a, RealFloat a) => INPM (SRGB i) a Source #

mkColorRGB :: Color RGB e -> Color (SRGB i l) e Source #

unColorRGB :: Color (SRGB i l) e -> Color RGB e Source #

(Illuminant i, Elevator e) => ColorSpace (SRGB i NonLinear) (i :: k) e Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Associated Types

type BaseModel (SRGB i NonLinear) :: Type Source #

type BaseSpace (SRGB i NonLinear) :: Type Source #

(Illuminant i, Elevator e) => ColorSpace (SRGB i Linear) (i :: k) e Source #

SRGB linear color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Associated Types

type BaseModel (SRGB i Linear) :: Type Source #

type BaseSpace (SRGB i Linear) :: Type Source #

Functor (Color (SRGB i l)) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

fmap :: (a -> b) -> Color (SRGB i l) a -> Color (SRGB i l) b #

(<$) :: a -> Color (SRGB i l) b -> Color (SRGB i l) a #

Applicative (Color (SRGB i l)) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

pure :: a -> Color (SRGB i l) a #

(<*>) :: Color (SRGB i l) (a -> b) -> Color (SRGB i l) a -> Color (SRGB i l) b #

liftA2 :: (a -> b -> c) -> Color (SRGB i l) a -> Color (SRGB i l) b -> Color (SRGB i l) c #

(*>) :: Color (SRGB i l) a -> Color (SRGB i l) b -> Color (SRGB i l) b #

(<*) :: Color (SRGB i l) a -> Color (SRGB i l) b -> Color (SRGB i l) a #

Foldable (Color (SRGB i l)) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

fold :: Monoid m => Color (SRGB i l) m -> m #

foldMap :: Monoid m => (a -> m) -> Color (SRGB i l) a -> m #

foldr :: (a -> b -> b) -> b -> Color (SRGB i l) a -> b #

foldr' :: (a -> b -> b) -> b -> Color (SRGB i l) a -> b #

foldl :: (b -> a -> b) -> b -> Color (SRGB i l) a -> b #

foldl' :: (b -> a -> b) -> b -> Color (SRGB i l) a -> b #

foldr1 :: (a -> a -> a) -> Color (SRGB i l) a -> a #

foldl1 :: (a -> a -> a) -> Color (SRGB i l) a -> a #

toList :: Color (SRGB i l) a -> [a] #

null :: Color (SRGB i l) a -> Bool #

length :: Color (SRGB i l) a -> Int #

elem :: Eq a => a -> Color (SRGB i l) a -> Bool #

maximum :: Ord a => Color (SRGB i l) a -> a #

minimum :: Ord a => Color (SRGB i l) a -> a #

sum :: Num a => Color (SRGB i l) a -> a #

product :: Num a => Color (SRGB i l) a -> a #

Traversable (Color (SRGB i l)) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

traverse :: Applicative f => (a -> f b) -> Color (SRGB i l) a -> f (Color (SRGB i l) b) #

sequenceA :: Applicative f => Color (SRGB i l) (f a) -> f (Color (SRGB i l) a) #

mapM :: Monad m => (a -> m b) -> Color (SRGB i l) a -> m (Color (SRGB i l) b) #

sequence :: Monad m => Color (SRGB i l) (m a) -> m (Color (SRGB i l) a) #

Eq e => Eq (Color (SRGB i l) e) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

(==) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

(/=) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

Ord e => Ord (Color (SRGB i l) e) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

compare :: Color (SRGB i l) e -> Color (SRGB i l) e -> Ordering #

(<) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

(<=) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

(>) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

(>=) :: Color (SRGB i l) e -> Color (SRGB i l) e -> Bool #

max :: Color (SRGB i l) e -> Color (SRGB i l) e -> Color (SRGB i l) e #

min :: Color (SRGB i l) e -> Color (SRGB i l) e -> Color (SRGB i l) e #

(Typeable l, Illuminant i, Elevator e) => Show (Color (SRGB i l) e) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

showsPrec :: Int -> Color (SRGB i l) e -> ShowS #

show :: Color (SRGB i l) e -> String #

showList :: [Color (SRGB i l) e] -> ShowS #

Storable e => Storable (Color (SRGB i l) e) Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Methods

sizeOf :: Color (SRGB i l) e -> Int #

alignment :: Color (SRGB i l) e -> Int #

peekElemOff :: Ptr (Color (SRGB i l) e) -> Int -> IO (Color (SRGB i l) e) #

pokeElemOff :: Ptr (Color (SRGB i l) e) -> Int -> Color (SRGB i l) e -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Color (SRGB i l) e) #

pokeByteOff :: Ptr b -> Int -> Color (SRGB i l) e -> IO () #

peek :: Ptr (Color (SRGB i l) e) -> IO (Color (SRGB i l) e) #

poke :: Ptr (Color (SRGB i l) e) -> Color (SRGB i l) e -> IO () #

Luma (SRGB i) Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

(Typeable l, Illuminant i, Elevator e) => ColorModel (SRGB i l) e Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

Associated Types

type Components (SRGB i l) e :: Type Source #

newtype Color (SRGB i l) e Source #

SRGB color space (derived)

Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

newtype Color (SRGB i l) e = SRGB (Color RGB e)
type BaseModel (SRGB i NonLinear) Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

type BaseModel (SRGB i Linear) Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

type BaseSpace (SRGB i NonLinear) Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

type BaseSpace (SRGB i Linear) Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

type Components (SRGB i l) e Source # 
Instance details

Defined in Graphics.Color.Space.RGB.Derived.SRGB

type Components (SRGB i l) e = (e, e, e)

primaries :: RealFloat e => Gamut rgb i e Source #

Primaries for ITU-R BT.709, which are also the primaries for sRGB color space.

Since: 0.1.0

transfer :: (Ord a, Floating a) => a -> a Source #

sRGB transfer function "gamma". This is a helper function, therefore ecctf should be used instead.

\[ \gamma(u) = \begin{cases} 12.92 u & u \leq 0.0031308 \\ 1.055 u^{1/2.4} - 0.055 & \text{otherwise} \end{cases} \]

Since: 0.1.0

itransfer :: (Ord a, Floating a) => a -> a Source #

sRGB inverse transfer function "gamma". This is a helper function, therefore dcctf should be used instead.

\[ \gamma^{-1}(u) = \begin{cases} u / 12.92 & u \leq 0.04045 \\ \left(\tfrac{u + 0.055}{1.055}\right)^{2.4} & \text{otherwise} \end{cases} \]

Since: 0.1.0