{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NegativeLiterals #-}
{-# LANGUAGE DataKinds #-}
module Graphics.Color.Illuminant.Wikipedia
( Degree2(..)
) where
import Graphics.Color.Space.Internal
instance Illuminant 'A where
type Temperature 'A = 2856
whitePoint :: WhitePoint 'A e
whitePoint = e -> e -> WhitePoint 'A e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.44757 e
0.40745
instance Illuminant 'B where
type Temperature 'B = 4874
whitePoint :: WhitePoint 'B e
whitePoint = e -> e -> WhitePoint 'B e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.34842 e
0.35161
instance Illuminant 'C where
type Temperature 'C = 6774
whitePoint :: WhitePoint 'C e
whitePoint = e -> e -> WhitePoint 'C e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.31006 e
0.31616
instance Illuminant 'D50 where
type Temperature 'D50 = 5003
whitePoint :: WhitePoint 'D50 e
whitePoint = e -> e -> WhitePoint 'D50 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.34567 e
0.35850
instance Illuminant 'D55 where
type Temperature 'D55 = 5503
whitePoint :: WhitePoint 'D55 e
whitePoint = e -> e -> WhitePoint 'D55 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.33242 e
0.34743
instance Illuminant 'D65 where
type Temperature 'D65 = 6504
whitePoint :: WhitePoint 'D65 e
whitePoint = e -> e -> WhitePoint 'D65 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.31271 e
0.32902
instance Illuminant 'D75 where
type Temperature 'D75 = 7504
whitePoint :: WhitePoint 'D75 e
whitePoint = e -> e -> WhitePoint 'D75 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.29902 e
0.31485
instance Illuminant 'E where
type Temperature 'E = 5454
whitePoint :: WhitePoint 'E e
whitePoint = e -> e -> WhitePoint 'E e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint (e
1 e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
3) (e
1 e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
3)
instance Illuminant 'F1 where
type Temperature 'F1 = 6430
whitePoint :: WhitePoint 'F1 e
whitePoint = e -> e -> WhitePoint 'F1 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.31310 e
0.33727
instance Illuminant 'F2 where
type Temperature 'F2 = 4230
whitePoint :: WhitePoint 'F2 e
whitePoint = e -> e -> WhitePoint 'F2 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.37208 e
0.37529
instance Illuminant 'F3 where
type Temperature 'F3 = 3450
whitePoint :: WhitePoint 'F3 e
whitePoint = e -> e -> WhitePoint 'F3 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.40910 e
0.39430
instance Illuminant 'F4 where
type Temperature 'F4 = 2940
whitePoint :: WhitePoint 'F4 e
whitePoint = e -> e -> WhitePoint 'F4 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.44018 e
0.40329
instance Illuminant 'F5 where
type Temperature 'F5 = 6350
whitePoint :: WhitePoint 'F5 e
whitePoint = e -> e -> WhitePoint 'F5 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.31379 e
0.34531
instance Illuminant 'F6 where
type Temperature 'F6 = 4150
whitePoint :: WhitePoint 'F6 e
whitePoint = e -> e -> WhitePoint 'F6 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.37790 e
0.38835
instance Illuminant 'F7 where
type Temperature 'F7 = 6500
whitePoint :: WhitePoint 'F7 e
whitePoint = e -> e -> WhitePoint 'F7 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.31292 e
0.32933
instance Illuminant 'F8 where
type Temperature 'F8 = 5000
whitePoint :: WhitePoint 'F8 e
whitePoint = e -> e -> WhitePoint 'F8 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.34588 e
0.35875
instance Illuminant 'F9 where
type Temperature 'F9 = 4150
whitePoint :: WhitePoint 'F9 e
whitePoint = e -> e -> WhitePoint 'F9 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.37417 e
0.37281
instance Illuminant 'F10 where
type Temperature 'F10 = 5000
whitePoint :: WhitePoint 'F10 e
whitePoint = e -> e -> WhitePoint 'F10 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.34609 e
0.35986
instance Illuminant 'F11 where
type Temperature 'F11 = 4000
whitePoint :: WhitePoint 'F11 e
whitePoint = e -> e -> WhitePoint 'F11 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.38052 e
0.37713
instance Illuminant 'F12 where
type Temperature 'F12 = 3000
whitePoint :: WhitePoint 'F12 e
whitePoint = e -> e -> WhitePoint 'F12 e
forall k e (i :: k). e -> e -> WhitePoint i e
WhitePoint e
0.43695 e
0.40441
data Degree2
= A
| B
| C
| D50
| D55
| D65
| D75
| E
| F1
| F2
| F3
| F4
| F5
| F6
| F7
| F8
| F9
| F10
| F11
| F12
deriving (Degree2 -> Degree2 -> Bool
(Degree2 -> Degree2 -> Bool)
-> (Degree2 -> Degree2 -> Bool) -> Eq Degree2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Degree2 -> Degree2 -> Bool
$c/= :: Degree2 -> Degree2 -> Bool
== :: Degree2 -> Degree2 -> Bool
$c== :: Degree2 -> Degree2 -> Bool
Eq, Int -> Degree2 -> ShowS
[Degree2] -> ShowS
Degree2 -> String
(Int -> Degree2 -> ShowS)
-> (Degree2 -> String) -> ([Degree2] -> ShowS) -> Show Degree2
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Degree2] -> ShowS
$cshowList :: [Degree2] -> ShowS
show :: Degree2 -> String
$cshow :: Degree2 -> String
showsPrec :: Int -> Degree2 -> ShowS
$cshowsPrec :: Int -> Degree2 -> ShowS
Show, ReadPrec [Degree2]
ReadPrec Degree2
Int -> ReadS Degree2
ReadS [Degree2]
(Int -> ReadS Degree2)
-> ReadS [Degree2]
-> ReadPrec Degree2
-> ReadPrec [Degree2]
-> Read Degree2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Degree2]
$creadListPrec :: ReadPrec [Degree2]
readPrec :: ReadPrec Degree2
$creadPrec :: ReadPrec Degree2
readList :: ReadS [Degree2]
$creadList :: ReadS [Degree2]
readsPrec :: Int -> ReadS Degree2
$creadsPrec :: Int -> ReadS Degree2
Read, Int -> Degree2
Degree2 -> Int
Degree2 -> [Degree2]
Degree2 -> Degree2
Degree2 -> Degree2 -> [Degree2]
Degree2 -> Degree2 -> Degree2 -> [Degree2]
(Degree2 -> Degree2)
-> (Degree2 -> Degree2)
-> (Int -> Degree2)
-> (Degree2 -> Int)
-> (Degree2 -> [Degree2])
-> (Degree2 -> Degree2 -> [Degree2])
-> (Degree2 -> Degree2 -> [Degree2])
-> (Degree2 -> Degree2 -> Degree2 -> [Degree2])
-> Enum Degree2
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Degree2 -> Degree2 -> Degree2 -> [Degree2]
$cenumFromThenTo :: Degree2 -> Degree2 -> Degree2 -> [Degree2]
enumFromTo :: Degree2 -> Degree2 -> [Degree2]
$cenumFromTo :: Degree2 -> Degree2 -> [Degree2]
enumFromThen :: Degree2 -> Degree2 -> [Degree2]
$cenumFromThen :: Degree2 -> Degree2 -> [Degree2]
enumFrom :: Degree2 -> [Degree2]
$cenumFrom :: Degree2 -> [Degree2]
fromEnum :: Degree2 -> Int
$cfromEnum :: Degree2 -> Int
toEnum :: Int -> Degree2
$ctoEnum :: Int -> Degree2
pred :: Degree2 -> Degree2
$cpred :: Degree2 -> Degree2
succ :: Degree2 -> Degree2
$csucc :: Degree2 -> Degree2
Enum, Degree2
Degree2 -> Degree2 -> Bounded Degree2
forall a. a -> a -> Bounded a
maxBound :: Degree2
$cmaxBound :: Degree2
minBound :: Degree2
$cminBound :: Degree2
Bounded)