Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Colour operations defined by the International Commission on Illumination (CIE).
Synopsis
- data Colour a
- cieXYZ :: Fractional a => a -> a -> a -> Colour a
- cieXYZView :: Fractional a => Colour a -> (a, a, a)
- luminance :: Fractional a => Colour a -> a
- toCIEXYZ :: Fractional a => Colour a -> (a, a, a)
- data Chromaticity a
- mkChromaticity :: Fractional a => a -> a -> Chromaticity a
- chromaCoords :: Fractional a => Chromaticity a -> (a, a, a)
- chromaX :: Fractional a => Chromaticity a -> a
- chromaY :: Fractional a => Chromaticity a -> a
- chromaZ :: Fractional a => Chromaticity a -> a
- chromaConvert :: (Fractional b, Real a) => Chromaticity a -> Chromaticity b
- chromaColour :: Fractional a => Chromaticity a -> a -> Colour a
- lightness :: (Ord a, Floating a) => Chromaticity a -> Colour a -> a
- cieLABView :: (Ord a, Floating a) => Chromaticity a -> Colour a -> (a, a, a)
- cieLAB :: (Ord a, Floating a) => Chromaticity a -> a -> a -> a -> Colour a
Documentation
This type represents the human preception of colour.
The a
parameter is a numeric type used internally for the
representation.
The Monoid
instance allows one to add colours, but beware that adding
colours can take you out of gamut. Consider using blend
whenever
possible.
Instances
cieXYZ :: Fractional a => a -> a -> a -> Colour a Source #
Construct a Colour
from XYZ coordinates for the 2° standard
(colourimetric) observer.
cieXYZView :: Fractional a => Colour a -> (a, a, a) Source #
Returns the XYZ colour coordinates for the 2° standard (colourimetric) observer.
luminance :: Fractional a => Colour a -> a Source #
Returns the Y colour coordinate (luminance) for the 2° standard (colourimetric) observer.
toCIEXYZ :: Fractional a => Colour a -> (a, a, a) Source #
Deprecated: toCIEXYZ
has been renamed cieXYZView
data Chromaticity a Source #
Instances
AffineSpace Chromaticity Source # | |
Defined in Data.Colour.CIE affineCombo :: Num a => [(a, Chromaticity a)] -> Chromaticity a -> Chromaticity a Source # | |
Eq a => Eq (Chromaticity a) Source # | |
Defined in Data.Colour.CIE.Chromaticity (==) :: Chromaticity a -> Chromaticity a -> Bool # (/=) :: Chromaticity a -> Chromaticity a -> Bool # | |
(Fractional a, Read a) => Read (Chromaticity a) Source # | |
Defined in Data.Colour.CIE.Chromaticity readsPrec :: Int -> ReadS (Chromaticity a) # readList :: ReadS [Chromaticity a] # readPrec :: ReadPrec (Chromaticity a) # readListPrec :: ReadPrec [Chromaticity a] # | |
(Fractional a, Show a) => Show (Chromaticity a) Source # | |
Defined in Data.Colour.CIE.Chromaticity showsPrec :: Int -> Chromaticity a -> ShowS # show :: Chromaticity a -> String # showList :: [Chromaticity a] -> ShowS # |
mkChromaticity :: Fractional a => a -> a -> Chromaticity a Source #
Constructs Chromaticity
from the CIE little x, little y
coordinates for the 2° standard (colourimetric) observer.
chromaCoords :: Fractional a => Chromaticity a -> (a, a, a) Source #
Returns the CIE little x, little y, little z coordinates for the 2° standard (colourimetric) observer.
chromaX :: Fractional a => Chromaticity a -> a Source #
Returns the CIE little x coordinate for the 2° standard (colourimetric) observer.
chromaY :: Fractional a => Chromaticity a -> a Source #
Returns the CIE little y coordinate for the 2° standard (colourimetric) observer.
chromaZ :: Fractional a => Chromaticity a -> a Source #
Returns the CIE little z coordinate for the 2° standard (colourimetric) observer.
chromaConvert :: (Fractional b, Real a) => Chromaticity a -> Chromaticity b Source #
Change the type used to represent the chromaticity coordinates.
:: Fractional a | |
=> Chromaticity a | |
-> a | |
-> Colour a |
Constructs a colour from the given Chromaticity
and luminance
.
:: (Ord a, Floating a) | |
=> Chromaticity a | White point |
-> Colour a | |
-> a |
Returns the lightness of a colour with respect to a given white point. Lightness is a perceptually uniform measure.
:: (Ord a, Floating a) | |
=> Chromaticity a | White point |
-> Colour a | |
-> (a, a, a) |
:: (Ord a, Floating a) | |
=> Chromaticity a | White point |
-> a | L* coordinate (lightness) |
-> a | a* coordinate |
-> a | b* coordinate |
-> Colour a |
Returns the colour for given CIELAB coordinates, which is a
perceptually uniform colour space.
If you don't know what white point to use, use
d65
.
Orphan instances
AffineSpace Chromaticity Source # | |
affineCombo :: Num a => [(a, Chromaticity a)] -> Chromaticity a -> Chromaticity a Source # |