{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Graphics.Vty.Attributes.Color
( Color(..)
, ColorMode(..)
, black
, red
, green
, yellow
, blue
, magenta
, cyan
, white
, brightBlack
, brightRed
, brightGreen
, brightYellow
, brightBlue
, brightMagenta
, brightCyan
, brightWhite
, linearColor
, srgbColor
, rgbColor
, color240
, module Graphics.Vty.Attributes.Color240
)
where
import Data.Word
import GHC.Generics
import Control.DeepSeq
import Graphics.Vty.Attributes.Color240
data Color = ISOColor !Word8 | Color240 !Word8 | RGBColor !Word8 !Word8 !Word8
deriving ( Color -> Color -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> String
$cshow :: Color -> String
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show, ReadPrec [Color]
ReadPrec Color
Int -> ReadS Color
ReadS [Color]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Color]
$creadListPrec :: ReadPrec [Color]
readPrec :: ReadPrec Color
$creadPrec :: ReadPrec Color
readList :: ReadS [Color]
$creadList :: ReadS [Color]
readsPrec :: Int -> ReadS Color
$creadsPrec :: Int -> ReadS Color
Read, forall x. Rep Color x -> Color
forall x. Color -> Rep Color x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Color x -> Color
$cfrom :: forall x. Color -> Rep Color x
Generic, Color -> ()
forall a. (a -> ()) -> NFData a
rnf :: Color -> ()
$crnf :: Color -> ()
NFData )
data ColorMode
= NoColor
| ColorMode8
| ColorMode16
| ColorMode240 !Word8
| FullColor
deriving ( ColorMode -> ColorMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorMode -> ColorMode -> Bool
$c/= :: ColorMode -> ColorMode -> Bool
== :: ColorMode -> ColorMode -> Bool
$c== :: ColorMode -> ColorMode -> Bool
Eq, Int -> ColorMode -> ShowS
[ColorMode] -> ShowS
ColorMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorMode] -> ShowS
$cshowList :: [ColorMode] -> ShowS
show :: ColorMode -> String
$cshow :: ColorMode -> String
showsPrec :: Int -> ColorMode -> ShowS
$cshowsPrec :: Int -> ColorMode -> ShowS
Show )
black, red, green, yellow, blue, magenta, cyan, white :: Color
black :: Color
black = Word8 -> Color
ISOColor Word8
0
red :: Color
red = Word8 -> Color
ISOColor Word8
1
green :: Color
green = Word8 -> Color
ISOColor Word8
2
yellow :: Color
yellow = Word8 -> Color
ISOColor Word8
3
blue :: Color
blue = Word8 -> Color
ISOColor Word8
4
magenta :: Color
magenta= Word8 -> Color
ISOColor Word8
5
cyan :: Color
cyan = Word8 -> Color
ISOColor Word8
6
white :: Color
white = Word8 -> Color
ISOColor Word8
7
brightBlack, brightRed, brightGreen, brightYellow :: Color
brightBlue, brightMagenta, brightCyan, brightWhite :: Color
brightBlack :: Color
brightBlack = Word8 -> Color
ISOColor Word8
8
brightRed :: Color
brightRed = Word8 -> Color
ISOColor Word8
9
brightGreen :: Color
brightGreen = Word8 -> Color
ISOColor Word8
10
brightYellow :: Color
brightYellow = Word8 -> Color
ISOColor Word8
11
brightBlue :: Color
brightBlue = Word8 -> Color
ISOColor Word8
12
brightMagenta :: Color
brightMagenta= Word8 -> Color
ISOColor Word8
13
brightCyan :: Color
brightCyan = Word8 -> Color
ISOColor Word8
14
brightWhite :: Color
brightWhite = Word8 -> Color
ISOColor Word8
15
linearColor :: Integral i => i -> i -> i -> Color
linearColor :: forall i. Integral i => i -> i -> i -> Color
linearColor i
r i
g i
b = Word8 -> Word8 -> Word8 -> Color
RGBColor Word8
r' Word8
g' Word8
b'
where
r' :: Word8
r' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> i
clamp i
r) :: Word8
g' :: Word8
g' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> i
clamp i
g) :: Word8
b' :: Word8
b' = forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> i
clamp i
b) :: Word8
clamp :: i -> i
clamp = forall a. Ord a => a -> a -> a
min i
255 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> a
max i
0
srgbColor :: Integral i => i -> i -> i -> Color
srgbColor :: forall i. Integral i => i -> i -> i -> Color
srgbColor i
r i
g i
b =
let shrink :: a -> Double
shrink a
n = forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n forall a. Fractional a => a -> a -> a
/ Double
255 :: Double
gamma :: a -> a
gamma a
u
| a
u forall a. Ord a => a -> a -> Bool
<= a
0.04045 = a
uforall a. Fractional a => a -> a -> a
/a
12.92
| Bool
otherwise = ((a
u forall a. Num a => a -> a -> a
+ a
0.055) forall a. Fractional a => a -> a -> a
/ a
1.055) forall a. Floating a => a -> a -> a
** a
2.4
expand :: a -> b
expand a
n = forall a b. (RealFrac a, Integral b) => a -> b
round (a
255 forall a. Num a => a -> a -> a
* a
n)
convert :: i -> Word8
convert = forall {a} {b}. (RealFrac a, Integral b) => a -> b
expand forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (Ord a, Floating a) => a -> a
gamma forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Integral a => a -> Double
shrink
in Word8 -> Word8 -> Word8 -> Color
RGBColor (i -> Word8
convert i
r) (i -> Word8
convert i
g) (i -> Word8
convert i
b)
color240 :: Integral i => i -> i -> i -> Color
color240 :: forall i. Integral i => i -> i -> i -> Color
color240 i
r i
g i
b = Word8 -> Color
Color240 (forall i. Integral i => i -> i -> i -> Word8
rgbColorToColor240 i
r i
g i
b)
rgbColor :: Integral i => i -> i -> i -> Color
rgbColor :: forall i. Integral i => i -> i -> i -> Color
rgbColor = forall i. Integral i => i -> i -> i -> Color
color240