{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Graphics.Color.Space.RGB.Alternative.HSI
( pattern ColorHSI
, pattern ColorHSIA
, pattern ColorH360SI
, HSI
, Color(HSI)
) where
import Data.Coerce
import Data.Proxy
import Foreign.Storable
import qualified Graphics.Color.Model.HSI as CM
import Graphics.Color.Model.Internal
import Graphics.Color.Space.Internal
import Graphics.Color.Space.RGB.Internal
data HSI cs
newtype instance Color (HSI cs) e = HSI (Color CM.HSI e)
deriving instance Eq e => Eq (Color (HSI cs) e)
deriving instance Ord e => Ord (Color (HSI cs) e)
deriving instance Functor (Color (HSI cs))
deriving instance Applicative (Color (HSI cs))
deriving instance Foldable (Color (HSI cs))
deriving instance Traversable (Color (HSI cs))
deriving instance Storable e => Storable (Color (HSI cs) e)
instance ColorModel cs e => Show (Color (HSI cs) e) where
showsPrec :: Int -> Color (HSI cs) e -> ShowS
showsPrec Int
_ = Color (HSI cs) e -> ShowS
forall cs e. ColorModel cs e => Color cs e -> ShowS
showsColorModel
pattern ColorHSI :: e -> e -> e -> Color (HSI cs) e
pattern $mColorHSI :: forall {r} {k} {e} {cs :: k}.
Color (HSI cs) e -> (e -> e -> e -> r) -> ((# #) -> r) -> r
$bColorHSI :: forall {k} e (cs :: k). e -> e -> e -> Color (HSI cs) e
ColorHSI h s i = HSI (CM.ColorHSI h s i)
{-# COMPLETE ColorHSI #-}
pattern ColorHSIA :: e -> e -> e -> e -> Color (Alpha (HSI cs)) e
pattern $mColorHSIA :: forall {r} {k} {e} {cs :: k}.
Color (Alpha (HSI cs)) e
-> (e -> e -> e -> e -> r) -> ((# #) -> r) -> r
$bColorHSIA :: forall {k} e (cs :: k).
e -> e -> e -> e -> Color (Alpha (HSI cs)) e
ColorHSIA h s i a = Alpha (HSI (CM.ColorHSI h s i)) a
{-# COMPLETE ColorHSIA #-}
pattern ColorH360SI :: Fractional e => e -> e -> e -> Color (HSI cs) e
pattern $mColorH360SI :: forall {r} {k} {e} {cs :: k}.
Fractional e =>
Color (HSI cs) e -> (e -> e -> e -> r) -> ((# #) -> r) -> r
$bColorH360SI :: forall {k} e (cs :: k).
Fractional e =>
e -> e -> e -> Color (HSI cs) e
ColorH360SI h s i <- ColorHSI ((* 360) -> h) s i where
ColorH360SI e
h e
s e
i = e -> e -> e -> Color (HSI cs) e
forall {k} e (cs :: k). e -> e -> e -> Color (HSI cs) e
ColorHSI (e
h e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
360) e
s e
i
{-# COMPLETE ColorH360SI #-}
instance ColorModel cs e => ColorModel (HSI cs) e where
type Components (HSI cs) e = (e, e, e)
type ChannelCount (HSI cs) = 3
channelCount :: Proxy (Color (HSI cs) e) -> Word8
channelCount Proxy (Color (HSI cs) e)
_ = Word8
3
{-# INLINE channelCount #-}
channelNames :: Proxy (Color (HSI cs) e) -> NonEmpty String
channelNames Proxy (Color (HSI cs) e)
_ = Proxy (Color HSI e) -> NonEmpty String
forall cs e.
ColorModel cs e =>
Proxy (Color cs e) -> NonEmpty String
channelNames (Proxy (Color HSI e)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Color CM.HSI e))
channelColors :: Proxy (Color (HSI cs) e) -> NonEmpty (V3 Word8)
channelColors Proxy (Color (HSI cs) e)
_ = Proxy (Color HSI e) -> NonEmpty (V3 Word8)
forall cs e.
ColorModel cs e =>
Proxy (Color cs e) -> NonEmpty (V3 Word8)
channelColors (Proxy (Color HSI e)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Color CM.HSI e))
toComponents :: Color (HSI cs) e -> Components (HSI cs) e
toComponents = Color HSI e -> (e, e, e)
Color HSI e -> Components HSI e
forall cs e. ColorModel cs e => Color cs e -> Components cs e
toComponents (Color HSI e -> (e, e, e))
-> (Color (HSI cs) e -> Color HSI e)
-> Color (HSI cs) e
-> (e, e, e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color (HSI cs) e -> Color HSI e
forall a b. Coercible a b => a -> b
coerce :: Color (HSI cs) e -> Color CM.HSI e)
{-# INLINE toComponents #-}
fromComponents :: Components (HSI cs) e -> Color (HSI cs) e
fromComponents = (Color HSI e -> Color (HSI cs) e
forall a b. Coercible a b => a -> b
coerce :: Color CM.HSI e -> Color (HSI cs) e) (Color HSI e -> Color (HSI cs) e)
-> ((e, e, e) -> Color HSI e) -> (e, e, e) -> Color (HSI cs) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e, e, e) -> Color HSI e
Components HSI e -> Color HSI e
forall cs e. ColorModel cs e => Components cs e -> Color cs e
fromComponents
{-# INLINE fromComponents #-}
showsColorModelName :: Proxy (Color (HSI cs) e) -> ShowS
showsColorModelName Proxy (Color (HSI cs) e)
_ = (String
"HSI-" String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy (Color cs e) -> ShowS
forall cs e. ColorModel cs e => Proxy (Color cs e) -> ShowS
showsColorModelName (Proxy (Color cs e)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Color cs e))
instance (ColorSpace (cs l) i e, RedGreenBlue cs i) => ColorSpace (HSI (cs l)) i e where
type BaseModel (HSI (cs l)) = CM.HSI
type BaseSpace (HSI (cs l)) = cs l
toBaseSpace :: ColorSpace (BaseSpace (HSI (cs l))) i e =>
Color (HSI (cs l)) e -> Color (BaseSpace (HSI (cs l))) e
toBaseSpace = Color RGB e -> Color (cs l) e
forall e (l :: Linearity). Color RGB e -> Color (cs 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 (cs l) e)
-> (Color (HSI (cs l)) e -> Color RGB e)
-> Color (HSI (cs l)) e
-> Color (cs l) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> e) -> Color RGB Double -> Color RGB e
forall a b. (a -> b) -> Color RGB a -> Color RGB b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> e
forall e. Elevator e => Double -> e
fromDouble (Color RGB Double -> Color RGB e)
-> (Color (HSI (cs l)) e -> Color RGB Double)
-> Color (HSI (cs l)) e
-> Color RGB e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color HSI Double -> Color RGB Double
forall e. (Ord e, Floating e) => Color HSI e -> Color RGB e
CM.hsi2rgb (Color HSI Double -> Color RGB Double)
-> (Color (HSI (cs l)) e -> Color HSI Double)
-> Color (HSI (cs l)) e
-> Color RGB Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> Double) -> Color HSI e -> Color HSI Double
forall a b. (a -> b) -> Color HSI a -> Color HSI b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> Double
forall e. Elevator e => e -> Double
toDouble (Color HSI e -> Color HSI Double)
-> (Color (HSI (cs l)) e -> Color HSI e)
-> Color (HSI (cs l)) e
-> Color HSI Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (HSI (cs l)) e -> Color HSI e
Color (HSI (cs l)) e -> Color (BaseModel (HSI (cs l))) e
forall k cs (i :: k) e.
ColorSpace cs i e =>
Color cs e -> Color (BaseModel cs) e
toBaseModel
{-# INLINE toBaseSpace #-}
fromBaseSpace :: ColorSpace (BaseSpace (HSI (cs l))) i e =>
Color (BaseSpace (HSI (cs l))) e -> Color (HSI (cs l)) e
fromBaseSpace = Color HSI e -> Color (HSI (cs l)) e
Color (BaseModel (HSI (cs l))) e -> Color (HSI (cs l)) e
forall k cs (i :: k) e.
ColorSpace cs i e =>
Color (BaseModel cs) e -> Color cs e
fromBaseModel (Color HSI e -> Color (HSI (cs l)) e)
-> (Color (cs l) e -> Color HSI e)
-> Color (cs l) e
-> Color (HSI (cs l)) e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> e) -> Color HSI Double -> Color HSI e
forall a b. (a -> b) -> Color HSI a -> Color HSI b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> e
forall e. Elevator e => Double -> e
fromDouble (Color HSI Double -> Color HSI e)
-> (Color (cs l) e -> Color HSI Double)
-> Color (cs l) e
-> Color HSI e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color RGB Double -> Color HSI Double
forall e. RealFloat e => Color RGB e -> Color HSI e
CM.rgb2hsi (Color RGB Double -> Color HSI Double)
-> (Color (cs l) e -> Color RGB Double)
-> Color (cs l) e
-> Color HSI Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> Double) -> Color RGB e -> Color RGB Double
forall a b. (a -> b) -> Color RGB a -> Color RGB b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> Double
forall e. Elevator e => e -> Double
toDouble (Color RGB e -> Color RGB Double)
-> (Color (cs l) e -> Color RGB e)
-> Color (cs l) e
-> Color RGB Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (cs l) e -> Color RGB e
forall k (cs :: Linearity -> *) (i :: k) (l :: Linearity) e.
RedGreenBlue cs i =>
Color (cs l) e -> Color RGB e
forall (l :: Linearity) e. Color (cs l) e -> Color RGB e
unColorRGB
{-# INLINE fromBaseSpace #-}
luminance :: forall a.
(Elevator a, RealFloat a) =>
Color (HSI (cs l)) e -> Color (Y i) a
luminance = Color (cs l) e -> Color (Y i) a
forall a.
(Elevator a, RealFloat a) =>
Color (cs l) e -> Color (Y i) a
forall k cs (i :: k) e a.
(ColorSpace cs i e, Elevator a, RealFloat a) =>
Color cs e -> Color (Y i) a
luminance (Color (cs l) e -> Color (Y i) a)
-> (Color (HSI (cs l)) e -> Color (cs l) e)
-> Color (HSI (cs l)) e
-> Color (Y i) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color (HSI (cs l)) e -> Color (cs l) e
Color (HSI (cs l)) e -> Color (BaseSpace (HSI (cs l))) e
forall k cs (i :: k) e.
(ColorSpace cs i e, ColorSpace (BaseSpace cs) i e) =>
Color cs e -> Color (BaseSpace cs) e
toBaseSpace
{-# INLINE luminance #-}
grayscale :: Color (HSI (cs l)) e -> Color X e
grayscale (Color (HSI (cs l)) e -> V3 e
forall a b. Coercible a b => a -> b
coerce -> V3 e
_ e
_ e
i) = e -> Color X e
forall e. e -> Color X e
X e
i
{-# INLINE grayscale #-}
replaceGrayscale :: Color (HSI (cs l)) e -> Color X e -> Color (HSI (cs l)) e
replaceGrayscale (Color (HSI (cs l)) e -> V3 e
forall a b. Coercible a b => a -> b
coerce -> V3 e
h e
s e
_) (X e
i) = V3 e -> Color (HSI (cs l)) e
forall a b. Coercible a b => a -> b
coerce (e -> e -> e -> V3 e
forall a. a -> a -> a -> V3 a
V3 e
h e
s e
i)
{-# INLINE replaceGrayscale #-}