module Data.Colour.SRGB
(Colour, RGB(..)
,sRGB24, sRGBBounded, sRGB
,toSRGB24, toSRGBBounded, toSRGB
,sRGB24shows, sRGB24show
,sRGB24reads, sRGB24read
,sRGBSpace
)
where
import Data.Word
import Numeric
import Data.Colour.Internal (quantize)
import Data.Colour.SRGB.Linear
import Data.Colour.RGBSpace hiding (transferFunction)
transferFunction lin | lin == 1 = 1
| lin <= 0.0031308 = 12.92*lin
| otherwise = (1 + a)*lin**(1/2.4) a
where
a = 0.055
invTransferFunction nonLin | nonLin == 1 = 1
| nonLin <= 0.04045 = nonLin/12.92
| otherwise =
((nonLin + a)/(1 + a))**2.4
where
a = 0.055
sRGB :: (Ord b, Floating b) => b -> b -> b -> Colour b
sRGB = curryRGB (uncurryRGB rgb . fmap invTransferFunction)
sRGBBounded :: (Ord b, Floating b, Integral a, Bounded a) =>
a -> a -> a -> Colour b
sRGBBounded r' g' b' = uncurryRGB sRGB (fmap f (RGB r' g' b'))
where
f x' = (fromIntegral x'/m)
m = fromIntegral $ maxBound `asTypeOf` r'
sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b
sRGB24 = sRGBBounded
toSRGB :: (Ord b, Floating b) => Colour b -> RGB b
toSRGB c = fmap transferFunction (toRGB c)
toSRGBBounded :: (RealFrac b, Floating b, Integral a, Bounded a) =>
Colour b -> RGB a
toSRGBBounded c = fmap f (toSRGB c)
where
f x' = quantize (m*x')
m = fromIntegral $ maxBound `asTypeOf` (f undefined)
toSRGB24 :: (RealFrac b, Floating b) => Colour b -> RGB Word8
toSRGB24 = toSRGBBounded
sRGB24shows :: (RealFrac b, Floating b) => Colour b -> ShowS
sRGB24shows c =
("#"++) . showHex2 r' . showHex2 g' . showHex2 b'
where
RGB r' g' b' = toSRGB24 c
showHex2 x | x <= 0xf = ("0"++) . showHex x
| otherwise = showHex x
sRGB24show :: (RealFrac b, Floating b) => Colour b -> String
sRGB24show x = sRGB24shows x ""
sRGB24reads :: (Ord b, Floating b) => ReadS (Colour b)
sRGB24reads "" = []
sRGB24reads x =
[(sRGB24 a b c, c0)
|(a,a0) <- readPair x', (b,b0) <- readPair a0, (c,c0) <- readPair b0]
where
x' | head x == '#' = tail x
| otherwise = x
readPair [] = []
readPair [_] = []
readPair a = [(x,a1)|(x,"") <- readHex a0]
where
(a0,a1) = splitAt 2 a
sRGB24read :: (Ord b, Floating b) => String -> (Colour b)
sRGB24read x | length rx /= 1 || not (null (snd (head rx))) =
error "Data.Colour.SRGB.sRGB24read: no parse"
| otherwise = fst (head rx)
where
rx = sRGB24reads x
sRGBSpace :: (Ord a, Floating a) => RGBSpace a
sRGBSpace = mkRGBSpace sRGBGamut transfer
where
transfer = TransferFunction transferFunction invTransferFunction (recip 2.2)