module Data.Colour.RGB where
import Data.List
import Data.Colour.Matrix
import Data.Colour.CIE.Chromaticity
import Control.Applicative
data RGB a = RGB {channelRed :: !a
                 ,channelGreen :: !a
                 ,channelBlue :: !a
                 } deriving (Eq, Show, Read)
instance Functor RGB where
 fmap f (RGB r g b) = RGB (f r) (f g) (f b)
instance Applicative RGB where
 pure c = RGB c c c
 (RGB fr fg fb) <*> (RGB r g b) = RGB (fr r) (fg g) (fb b)
uncurryRGB :: (a -> a -> a -> b) -> RGB a -> b
uncurryRGB f (RGB r g b) = f r g b
curryRGB :: (RGB a -> b) -> a -> a -> a -> b
curryRGB f r g b = f (RGB r g b)
data RGBGamut = RGBGamut {primaries :: !(RGB (Chromaticity Rational))
                         ,whitePoint :: !(Chromaticity Rational)
                         } deriving (Eq)
instance Show RGBGamut where
  showsPrec d gamut = showParen (d > app_prec) showStr
   where
    showStr = showString "mkRGBGamut"
            . showString " " . (showsPrec (app_prec+1) (primaries gamut))
            . showString " " . (showsPrec (app_prec+1) (whitePoint gamut))
instance Read RGBGamut where
  readsPrec d r = readParen (d > app_prec)
                  (\r -> [(mkRGBGamut p w,t)
                         |("mkRGBGamut",s) <- lex r
                         ,(p,s0) <- readsPrec (app_prec+1) s
                         ,(w,t)  <- readsPrec (app_prec+1) s0]) r
mkRGBGamut :: RGB (Chromaticity Rational) 
           -> Chromaticity Rational       
           -> RGBGamut
mkRGBGamut = RGBGamut
primaryMatrix :: (Fractional a) => (RGB (Chromaticity a)) -> [[a]]
primaryMatrix p =
  [[xr, xg, xb]
  ,[yr, yg, yb]
  ,[zr, zg, zb]]
 where
  RGB (xr, yr, zr)
      (xg, yg, zg)
      (xb, yb, zb) = fmap chromaCoords p
rgb2xyz :: RGBGamut -> [[Rational]]
rgb2xyz space =
  transpose (zipWith (map . (*)) as (transpose matrix))
 where
  (xn, yn, zn) = chromaCoords (whitePoint space)
  matrix = primaryMatrix (primaries space)
  as = mult (inverse matrix) [xn/yn, 1, zn/yn]
xyz2rgb :: RGBGamut -> [[Rational]]
xyz2rgb = inverse . rgb2xyz
hslsv :: (Fractional a, Ord a) => RGB a -> (a,a,a,a,a)
hslsv (RGB r g b) | mx == mn  = (0,0,mx,0 ,mx)
                  | otherwise = (h,s,l ,s0,mx)
 where
  mx = maximum [r,g,b]
  mn = minimum [r,g,b]
  l = (mx+mn)/2
  s | l <= 0.5 = (mx-mn)/(mx+mn)
    | otherwise = (mx-mn)/(2-(mx+mn))
  s0 = (mx-mn)/mx
  
  [x,y,z] = take 3 $ dropWhile (/=mx) [r,g,b,r,g]
  Just o = elemIndex mx [r,g,b]
  h0 = 60*(y-z)/(mx-mn) + 120*(fromIntegral o)
  h | h0 < 0 = h0 + 360
    | otherwise = h0
hue :: (Fractional a, Ord a) => RGB a -> a
hue rgb = h
 where
  (h,_,_,_,_) = hslsv rgb
mod1 x | pf < 0 = pf+1
       | otherwise = pf
 where
  (_,pf) = properFraction x