module Data.Colour.CIE.Chromaticity where
data Chromaticity a = Chroma !a !a deriving (Chromaticity a -> Chromaticity a -> Bool
(Chromaticity a -> Chromaticity a -> Bool)
-> (Chromaticity a -> Chromaticity a -> Bool)
-> Eq (Chromaticity a)
forall a. Eq a => Chromaticity a -> Chromaticity a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chromaticity a -> Chromaticity a -> Bool
$c/= :: forall a. Eq a => Chromaticity a -> Chromaticity a -> Bool
== :: Chromaticity a -> Chromaticity a -> Bool
$c== :: forall a. Eq a => Chromaticity a -> Chromaticity a -> Bool
Eq)
mkChromaticity :: (Fractional a) => a -> a -> Chromaticity a
mkChromaticity :: a -> a -> Chromaticity a
mkChromaticity = a -> a -> Chromaticity a
forall a. a -> a -> Chromaticity a
Chroma
chromaCoords :: (Fractional a) => Chromaticity a -> (a, a, a)
chromaCoords :: Chromaticity a -> (a, a, a)
chromaCoords (Chroma a
x a
y) = (a
x, a
y, a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
y)
chromaX :: (Fractional a) => Chromaticity a -> a
chromaX :: Chromaticity a -> a
chromaX (Chroma a
x a
_y) = a
x
chromaY :: (Fractional a) => Chromaticity a -> a
chromaY :: Chromaticity a -> a
chromaY (Chroma a
_x a
y) = a
y
chromaZ :: (Fractional a) => Chromaticity a -> a
chromaZ :: Chromaticity a -> a
chromaZ (Chroma a
x a
y) = a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
y
chromaConvert :: (Fractional b, Real a) => Chromaticity a -> Chromaticity b
chromaConvert :: Chromaticity a -> Chromaticity b
chromaConvert (Chroma a
x a
y) = b -> b -> Chromaticity b
forall a. a -> a -> Chromaticity a
Chroma (a -> b
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
x) (a -> b
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
y)
instance (Fractional a, Show a) => Show (Chromaticity a) where
showsPrec :: Int -> Chromaticity a -> ShowS
showsPrec Int
d Chromaticity a
c = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
app_prec) ShowS
showStr
where
showStr :: ShowS
showStr = String -> ShowS
showString String
"mkChromaticity " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec (Int
app_precInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) a
x)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec (Int
app_precInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) a
y)
(a
x,a
y,a
z) = Chromaticity a -> (a, a, a)
forall a. Fractional a => Chromaticity a -> (a, a, a)
chromaCoords Chromaticity a
c
instance (Fractional a, Read a) => Read (Chromaticity a) where
readsPrec :: Int -> ReadS (Chromaticity a)
readsPrec Int
d String
r = Bool -> ReadS (Chromaticity a) -> ReadS (Chromaticity a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
app_prec)
(\String
r -> [(a -> a -> Chromaticity a
forall a. Fractional a => a -> a -> Chromaticity a
mkChromaticity a
x a
y,String
t)
|(String
"mkChromaticity",String
s) <- ReadS String
lex String
r
,(a
x,String
s0) <- Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec (Int
app_precInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) String
s
,(a
y,String
t) <- Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec (Int
app_precInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) String
s0]) String
r
app_prec :: Int
app_prec = Int
10
infix_prec :: Int
infix_prec = Int
9 Int -> Int -> Int
forall a. a -> a -> a
`asTypeOf` Int
app_prec