{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NegativeLiterals #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
-- |
-- Module      : Graphics.Color.Space.RGB.AdobeRGB
-- Copyright   : (c) Alexey Kuleshevich 2019-2020
-- License     : BSD3
-- Maintainer  : Alexey Kuleshevich <lehins@yandex.ru>
-- Stability   : experimental
-- Portability : non-portable
--
module Graphics.Color.Space.RGB.AdobeRGB
  ( -- * Constructors for a AdobeRGB color space.
    pattern AdobeRGB
  , pattern ColorAdobeRGB
  , pattern ColorAdobeRGBA
  , AdobeRGB
  , D65
  ) where

import Data.Typeable
import Foreign.Storable
import Graphics.Color.Model.Internal
import qualified Graphics.Color.Model.RGB as CM
import Graphics.Color.Space.Internal
import Graphics.Color.Space.RGB.Internal
import Graphics.Color.Space.RGB.ITU.Rec601 (D65)


-- | A very common [AdobeRGB (1998)](https://en.wikipedia.org/wiki/Adobe_RGB_color_space)
-- color space with:
--
-- * `D65` illuminant
--
-- * Transfer function:
--
-- \[
-- \gamma(u) = u^{2.19921875} = u^\frac{563}{256}
-- \]
--
-- * Inverse transfer function:
--
-- \[
-- \gamma^{-1}(u) = u^\frac{1}{2.19921875} = u^\frac{256}{563}
-- \]
--
-- * Normalized primary matrix:
--
-- >>> :set -XDataKinds
-- >>> import Graphics.Color.Space.RGB.AdobeRGB
-- >>> npm :: NPM AdobeRGB Float
-- [ [ 0.57667000, 0.18556000, 0.18823000 ]
-- , [ 0.29734000, 0.62736000, 0.07529000 ]
-- , [ 0.02703000, 0.07069000, 0.99134000 ] ]
--
-- * Inverse normalized primary matrix:
--
-- >>> :set -XDataKinds
-- >>> import Graphics.Color.Space.RGB.AdobeRGB
-- >>> inpm :: INPM AdobeRGB Float
-- [ [ 2.04159000,-0.56501000,-0.34473000 ]
-- , [-0.96924000, 1.87597000, 0.04156000 ]
-- , [ 0.01344000,-0.11836000, 1.01517000 ] ]
--
-- @since 0.1.0
data AdobeRGB (l :: Linearity)

newtype instance Color (AdobeRGB l) e = AdobeRGB (Color CM.RGB e)

-- | Constructor for a color in @AdobeRGB@ color space
--
-- @since 0.1.0
pattern ColorAdobeRGB :: e -> e -> e -> Color (AdobeRGB l) e
pattern $bColorAdobeRGB :: e -> e -> e -> Color (AdobeRGB l) e
$mColorAdobeRGB :: forall r e (l :: Linearity).
Color (AdobeRGB l) e -> (e -> e -> e -> r) -> (Void# -> r) -> r
ColorAdobeRGB r g b = AdobeRGB (CM.ColorRGB r g b)
{-# COMPLETE ColorAdobeRGB #-}

-- | Constructor for a color in @AdobeRGB@ color space with alpha channel
--
-- @since 0.1.0
pattern ColorAdobeRGBA :: e -> e -> e -> e -> Color (Alpha (AdobeRGB l)) e
pattern $bColorAdobeRGBA :: e -> e -> e -> e -> Color (Alpha (AdobeRGB l)) e
$mColorAdobeRGBA :: forall r e (l :: Linearity).
Color (Alpha (AdobeRGB l)) e
-> (e -> e -> e -> e -> r) -> (Void# -> r) -> r
ColorAdobeRGBA r g b a = Alpha (AdobeRGB (CM.ColorRGB r g b)) a
{-# COMPLETE ColorAdobeRGBA #-}


-- | `AdobeRGB` color space
deriving instance Eq e => Eq (Color (AdobeRGB l) e)
-- | `AdobeRGB` color space
deriving instance Ord e => Ord (Color (AdobeRGB l) e)
-- | `AdobeRGB` color space
deriving instance Functor (Color (AdobeRGB l))
-- | `AdobeRGB` color space
deriving instance Applicative (Color (AdobeRGB l))
-- | `AdobeRGB` color space
deriving instance Foldable (Color (AdobeRGB l))
-- | `AdobeRGB` color space
deriving instance Traversable (Color (AdobeRGB l))
-- | `AdobeRGB` color space
deriving instance Storable e => Storable (Color (AdobeRGB l) e)

-- | `AdobeRGB` color space
instance (Typeable l, Elevator e) => Show (Color (AdobeRGB l) e) where
  showsPrec :: Int -> Color (AdobeRGB l) e -> ShowS
showsPrec Int
_ = Color (AdobeRGB l) e -> ShowS
forall cs e. ColorModel cs e => Color cs e -> ShowS
showsColorModel

-- | `AdobeRGB` color space
instance (Typeable l, Elevator e) => ColorModel (AdobeRGB l) e where
  type Components (AdobeRGB l) e = (e, e, e)
  toComponents :: Color (AdobeRGB l) e -> Components (AdobeRGB l) e
toComponents = Color RGB e -> (e, e, e)
forall cs e. ColorModel cs e => Color cs e -> Components cs e
toComponents (Color RGB e -> (e, e, e))
-> (Color (AdobeRGB l) e -> Color RGB e)
-> Color (AdobeRGB l) e
-> (e, e, e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (AdobeRGB l) e -> Color RGB e
forall k (cs :: Linearity -> *) (i :: k) (l :: Linearity) e.
RedGreenBlue cs i =>
Color (cs l) e -> Color RGB e
unColorRGB
  {-# INLINE toComponents #-}
  fromComponents :: Components (AdobeRGB l) e -> Color (AdobeRGB l) e
fromComponents = Color RGB e -> Color (AdobeRGB l) e
forall k (cs :: Linearity -> *) (i :: k) e (l :: Linearity).
RedGreenBlue cs i =>
Color RGB e -> Color (cs l) e
mkColorRGB (Color RGB e -> Color (AdobeRGB l) e)
-> ((e, e, e) -> Color RGB e) -> (e, e, e) -> Color (AdobeRGB l) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e, e, e) -> Color RGB e
forall cs e. ColorModel cs e => Components cs e -> Color cs e
fromComponents
  {-# INLINE fromComponents #-}

-- | `AdobeRGB` linear color space
instance Elevator e => ColorSpace (AdobeRGB 'Linear) D65 e where
  type BaseModel (AdobeRGB 'Linear) = CM.RGB
  toBaseSpace :: Color (AdobeRGB 'Linear) e
-> Color (BaseSpace (AdobeRGB 'Linear)) e
toBaseSpace = Color (AdobeRGB 'Linear) e
-> Color (BaseSpace (AdobeRGB 'Linear)) e
forall a. a -> a
id
  {-# INLINE toBaseSpace #-}
  fromBaseSpace :: Color (BaseSpace (AdobeRGB 'Linear)) e
-> Color (AdobeRGB 'Linear) e
fromBaseSpace = Color (BaseSpace (AdobeRGB 'Linear)) e
-> Color (AdobeRGB 'Linear) e
forall a. a -> a
id
  {-# INLINE fromBaseSpace #-}
  luminance :: Color (AdobeRGB 'Linear) e -> Color (Y D65) a
luminance = Color (AdobeRGB 'Linear) a -> Color (Y D65) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (cs 'Linear) e -> Color (Y i) e
rgbLinearLuminance (Color (AdobeRGB 'Linear) a -> Color (Y D65) a)
-> (Color (AdobeRGB 'Linear) e -> Color (AdobeRGB 'Linear) a)
-> Color (AdobeRGB 'Linear) e
-> Color (Y D65) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> a)
-> Color (AdobeRGB 'Linear) e -> Color (AdobeRGB 'Linear) a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> a
forall e a. (Elevator e, Elevator a, RealFloat a) => e -> a
toRealFloat
  {-# INLINE luminance #-}
  toColorXYZ :: Color (AdobeRGB 'Linear) e -> Color (XYZ D65) a
toColorXYZ = Color (AdobeRGB 'Linear) a -> Color (XYZ D65) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'NonLinear) i e,
 ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (cs 'Linear) e -> Color (XYZ i) e
rgbLinear2xyz (Color (AdobeRGB 'Linear) a -> Color (XYZ D65) a)
-> (Color (AdobeRGB 'Linear) e -> Color (AdobeRGB 'Linear) a)
-> Color (AdobeRGB 'Linear) e
-> Color (XYZ D65) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> a)
-> Color (AdobeRGB 'Linear) e -> Color (AdobeRGB 'Linear) a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> a
forall e a. (Elevator e, Elevator a, RealFloat a) => e -> a
toRealFloat
  {-# INLINE toColorXYZ #-}
  fromColorXYZ :: Color (XYZ D65) a -> Color (AdobeRGB 'Linear) e
fromColorXYZ = (a -> e)
-> Color (AdobeRGB 'Linear) a -> Color (AdobeRGB 'Linear) e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> e
forall e a. (Elevator e, Elevator a, RealFloat a) => a -> e
fromRealFloat (Color (AdobeRGB 'Linear) a -> Color (AdobeRGB 'Linear) e)
-> (Color (XYZ D65) a -> Color (AdobeRGB 'Linear) a)
-> Color (XYZ D65) a
-> Color (AdobeRGB 'Linear) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (XYZ D65) a -> Color (AdobeRGB 'Linear) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'NonLinear) i e,
 ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (XYZ i) e -> Color (cs 'Linear) e
xyz2rgbLinear
  {-# INLINE fromColorXYZ #-}

-- | `AdobeRGB` color space
instance Elevator e => ColorSpace (AdobeRGB 'NonLinear) D65 e where
  type BaseModel (AdobeRGB 'NonLinear) = CM.RGB
  toBaseSpace :: Color (AdobeRGB 'NonLinear) e
-> Color (BaseSpace (AdobeRGB 'NonLinear)) e
toBaseSpace = Color (AdobeRGB 'NonLinear) e
-> Color (BaseSpace (AdobeRGB 'NonLinear)) e
forall a. a -> a
id
  {-# INLINE toBaseSpace #-}
  fromBaseSpace :: Color (BaseSpace (AdobeRGB 'NonLinear)) e
-> Color (AdobeRGB 'NonLinear) e
fromBaseSpace = Color (BaseSpace (AdobeRGB 'NonLinear)) e
-> Color (AdobeRGB 'NonLinear) e
forall a. a -> a
id
  {-# INLINE fromBaseSpace #-}
  luminance :: Color (AdobeRGB 'NonLinear) e -> Color (Y D65) a
luminance = Color (AdobeRGB 'NonLinear) a -> Color (Y D65) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (cs 'NonLinear) e -> Color (Y i) e
rgbLuminance (Color (AdobeRGB 'NonLinear) a -> Color (Y D65) a)
-> (Color (AdobeRGB 'NonLinear) e -> Color (AdobeRGB 'NonLinear) a)
-> Color (AdobeRGB 'NonLinear) e
-> Color (Y D65) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> a)
-> Color (AdobeRGB 'NonLinear) e -> Color (AdobeRGB 'NonLinear) a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> a
forall e a. (Elevator e, Elevator a, RealFloat a) => e -> a
toRealFloat
  {-# INLINE luminance #-}
  toColorXYZ :: Color (AdobeRGB 'NonLinear) e -> Color (XYZ D65) a
toColorXYZ = Color (AdobeRGB 'NonLinear) a -> Color (XYZ D65) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'NonLinear) i e,
 ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (cs 'NonLinear) e -> Color (XYZ i) e
rgb2xyz (Color (AdobeRGB 'NonLinear) a -> Color (XYZ D65) a)
-> (Color (AdobeRGB 'NonLinear) e -> Color (AdobeRGB 'NonLinear) a)
-> Color (AdobeRGB 'NonLinear) e
-> Color (XYZ D65) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> a)
-> Color (AdobeRGB 'NonLinear) e -> Color (AdobeRGB 'NonLinear) a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> a
forall e a. (Elevator e, Elevator a, RealFloat a) => e -> a
toRealFloat
  {-# INLINE toColorXYZ #-}
  fromColorXYZ :: Color (XYZ D65) a -> Color (AdobeRGB 'NonLinear) e
fromColorXYZ = (a -> e)
-> Color (AdobeRGB 'NonLinear) a -> Color (AdobeRGB 'NonLinear) e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> e
forall e a. (Elevator e, Elevator a, RealFloat a) => a -> e
fromRealFloat (Color (AdobeRGB 'NonLinear) a -> Color (AdobeRGB 'NonLinear) e)
-> (Color (XYZ D65) a -> Color (AdobeRGB 'NonLinear) a)
-> Color (XYZ D65) a
-> Color (AdobeRGB 'NonLinear) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (XYZ D65) a -> Color (AdobeRGB 'NonLinear) a
forall k (cs :: Linearity -> *) (i :: k) e.
(RedGreenBlue cs i, ColorSpace (cs 'NonLinear) i e,
 ColorSpace (cs 'Linear) i e, RealFloat e) =>
Color (XYZ i) e -> Color (cs 'NonLinear) e
xyz2rgb
  {-# INLINE fromColorXYZ #-}

-- | `AdobeRGB` color space
instance RedGreenBlue AdobeRGB D65 where
  gamut :: Gamut AdobeRGB D65 e
gamut = Primary D65 e
-> Primary D65 e -> Primary D65 e -> Gamut AdobeRGB D65 e
forall k (cs :: Linearity -> *) (i :: k) e.
Primary i e -> Primary i e -> Primary i e -> Gamut cs i e
Gamut (e -> e -> Primary D65 e
forall k e (i :: k). e -> e -> Primary i e
Primary e
0.64 e
0.33)
                (e -> e -> Primary D65 e
forall k e (i :: k). e -> e -> Primary i e
Primary e
0.21 e
0.71)
                (e -> e -> Primary D65 e
forall k e (i :: k). e -> e -> Primary i e
Primary e
0.15 e
0.06)
  transfer :: e -> e
transfer e
u = e
u e -> e -> e
forall a. Floating a => a -> a -> a
** (e
256 e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
563)
  {-# INLINE transfer #-}
  itransfer :: e -> e
itransfer e
u = e
u e -> e -> e
forall a. Floating a => a -> a -> a
** e
2.19921875 -- in rational form 563/256
  {-# INLINE itransfer #-}
  npm :: NPM AdobeRGB e
npm = M3x3 e -> NPM AdobeRGB e
forall k (cs :: k) e. M3x3 e -> NPM cs e
NPM (M3x3 e -> NPM AdobeRGB e) -> M3x3 e -> NPM AdobeRGB e
forall a b. (a -> b) -> a -> b
$ V3 e -> V3 e -> V3 e -> M3x3 e
forall a. V3 a -> V3 a -> V3 a -> M3x3 a
M3x3 (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3 e
0.57667 e
0.18556 e
0.18823)
                   (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3 e
0.29734 e
0.62736 e
0.07529)
                   (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3 e
0.02703 e
0.07069 e
0.99134)
  inpm :: INPM AdobeRGB e
inpm = M3x3 e -> INPM AdobeRGB e
forall k (cs :: k) e. M3x3 e -> INPM cs e
INPM (M3x3 e -> INPM AdobeRGB e) -> M3x3 e -> INPM AdobeRGB e
forall a b. (a -> b) -> a -> b
$ V3 e -> V3 e -> V3 e -> M3x3 e
forall a. V3 a -> V3 a -> V3 a -> M3x3 a
M3x3 (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3  e
2.04159 e
-0.56501 e
-0.34473)
                     (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3 e
-0.96924  e
1.87597  e
0.04156)
                     (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3  e
0.01344 e
-0.11836  e
1.01517)