{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Graphics.Color.Model.HSI
( HSI
, pattern ColorHSI
, pattern ColorHSIA
, pattern ColorH360SI
, Color
, ColorModel(..)
, hsi2rgb
, rgb2hsi
) where
import Foreign.Storable
import Graphics.Color.Model.Internal
import Graphics.Color.Model.RGB
data HSI
newtype instance Color HSI e = HSI (V3 e)
pattern ColorHSI :: e -> e -> e -> Color HSI e
pattern $bColorHSI :: e -> e -> e -> Color HSI e
$mColorHSI :: forall r e. Color HSI e -> (e -> e -> e -> r) -> (Void# -> r) -> r
ColorHSI h s i = HSI (V3 h s i)
{-# COMPLETE ColorHSI #-}
pattern ColorHSIA :: e -> e -> e -> e -> Color (Alpha HSI) e
pattern $bColorHSIA :: e -> e -> e -> e -> Color (Alpha HSI) e
$mColorHSIA :: forall r e.
Color (Alpha HSI) e -> (e -> e -> e -> e -> r) -> (Void# -> r) -> r
ColorHSIA h s i a = Alpha (ColorHSI h s i) a
{-# COMPLETE ColorHSIA #-}
pattern ColorH360SI :: Fractional e => e -> e -> e -> Color HSI e
pattern $bColorH360SI :: e -> e -> e -> Color HSI e
$mColorH360SI :: forall r e.
Fractional e =>
Color HSI e -> (e -> e -> e -> r) -> (Void# -> r) -> r
ColorH360SI h s i <- ColorHSI ((* 360) -> h) s i where
ColorH360SI e
h e
s e
i = e -> e -> e -> Color HSI e
forall e. e -> e -> e -> Color HSI e
ColorHSI (e
h e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
360) e
s e
i
{-# COMPLETE ColorH360SI #-}
deriving instance Eq e => Eq (Color HSI e)
deriving instance Ord e => Ord (Color HSI e)
deriving instance Functor (Color HSI)
deriving instance Applicative (Color HSI)
deriving instance Foldable (Color HSI)
deriving instance Traversable (Color HSI)
deriving instance Storable e => Storable (Color HSI e)
instance Elevator e => Show (Color HSI e) where
showsPrec :: Int -> Color HSI e -> ShowS
showsPrec Int
_ = Color HSI e -> ShowS
forall cs e. ColorModel cs e => Color cs e -> ShowS
showsColorModel
instance Elevator e => ColorModel HSI e where
type Components HSI e = (e, e, e)
toComponents :: Color HSI e -> Components HSI e
toComponents (ColorHSI e
h e
s e
i) = (e
h, e
s, e
i)
{-# INLINE toComponents #-}
fromComponents :: Components HSI e -> Color HSI e
fromComponents (h, s, i) = e -> e -> e -> Color HSI e
forall e. e -> e -> e -> Color HSI e
ColorHSI e
h e
s e
i
{-# INLINE fromComponents #-}
hsi2rgb :: (Ord e, Floating e) => Color HSI e -> Color RGB e
hsi2rgb :: Color HSI e -> Color RGB e
hsi2rgb (ColorHSI e
h' e
s e
i) = e -> Color RGB e
getRGB (e
h' e -> e -> e
forall a. Num a => a -> a -> a
* e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
forall a. Floating a => a
pi)
where
!is :: e
is = e
i e -> e -> e
forall a. Num a => a -> a -> a
* e
s
!second :: e
second = e
i e -> e -> e
forall a. Num a => a -> a -> a
- e
is
!pi3 :: e
pi3 = e
forall a. Floating a => a
pi e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
3
getFirst :: e -> e -> e
getFirst !e
a !e
b = e
i e -> e -> e
forall a. Num a => a -> a -> a
+ e
is e -> e -> e
forall a. Num a => a -> a -> a
* e -> e
forall a. Floating a => a -> a
cos e
a e -> e -> e
forall a. Fractional a => a -> a -> a
/ e -> e
forall a. Floating a => a -> a
cos e
b
{-# INLINE getFirst #-}
getThird :: e -> e -> e
getThird !e
v1 !e
v2 = e
i e -> e -> e
forall a. Num a => a -> a -> a
+ e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
is e -> e -> e
forall a. Num a => a -> a -> a
+ e
v1 e -> e -> e
forall a. Num a => a -> a -> a
- e
v2
{-# INLINE getThird #-}
getRGB :: e -> Color RGB e
getRGB e
h
| e
h e -> e -> Bool
forall a. Ord a => a -> a -> Bool
< e
0 = e -> e -> e -> Color RGB e
forall e. e -> e -> e -> Color RGB e
ColorRGB e
0 e
0 e
0
| e
h e -> e -> Bool
forall a. Ord a => a -> a -> Bool
< e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
pi3 =
let !r :: e
r = e -> e -> e
getFirst e
h (e
pi3 e -> e -> e
forall a. Num a => a -> a -> a
- e
h)
!b :: e
b = e
second
!g :: e
g = e -> e -> e
getThird e
b e
r
in e -> e -> e -> Color RGB e
forall e. e -> e -> e -> Color RGB e
ColorRGB e
r e
g e
b
| e
h e -> e -> Bool
forall a. Ord a => a -> a -> Bool
< e
4 e -> e -> e
forall a. Num a => a -> a -> a
* e
pi3 =
let !g :: e
g = e -> e -> e
getFirst (e
h e -> e -> e
forall a. Num a => a -> a -> a
- e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
pi3) (e
h e -> e -> e
forall a. Num a => a -> a -> a
+ e
forall a. Floating a => a
pi)
!r :: e
r = e
second
!b :: e
b = e -> e -> e
getThird e
r e
g
in e -> e -> e -> Color RGB e
forall e. e -> e -> e -> Color RGB e
ColorRGB e
r e
g e
b
| e
h e -> e -> Bool
forall a. Ord a => a -> a -> Bool
< e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
forall a. Floating a => a
pi =
let !b :: e
b = e -> e -> e
getFirst (e
h e -> e -> e
forall a. Num a => a -> a -> a
- e
4 e -> e -> e
forall a. Num a => a -> a -> a
* e
pi3) (e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
forall a. Floating a => a
pi e -> e -> e
forall a. Num a => a -> a -> a
- e
pi3 e -> e -> e
forall a. Num a => a -> a -> a
- e
h)
!g :: e
g = e
second
!r :: e
r = e -> e -> e
getThird e
g e
b
in e -> e -> e -> Color RGB e
forall e. e -> e -> e -> Color RGB e
ColorRGB e
r e
g e
b
| Bool
otherwise = e -> e -> e -> Color RGB e
forall e. e -> e -> e -> Color RGB e
ColorRGB e
0 e
0 e
0
{-# INLINE getRGB #-}
{-# INLINE hsi2rgb #-}
rgb2hsi :: RealFloat e => Color RGB e -> Color HSI e
rgb2hsi :: Color RGB e -> Color HSI e
rgb2hsi (ColorRGB e
r e
g e
b) = e -> e -> e -> Color HSI e
forall e. e -> e -> e -> Color HSI e
ColorHSI e
h e
s e
i
where
!h' :: e
h' = e -> e -> e
forall a. RealFloat a => a -> a -> a
atan2 e
y e
x
!h'2pi :: e
h'2pi = e
h' e -> e -> e
forall a. Fractional a => a -> a -> a
/ (e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
forall a. Floating a => a
pi)
!h :: e
h
| e
h' e -> e -> Bool
forall a. Ord a => a -> a -> Bool
< e
0 = e
h'2pi e -> e -> e
forall a. Num a => a -> a -> a
+ e
1
| Bool
otherwise = e
h'2pi
!s :: e
s
| e
i e -> e -> Bool
forall a. Eq a => a -> a -> Bool
== e
0 = e
0
| Bool
otherwise = e
1 e -> e -> e
forall a. Num a => a -> a -> a
- e -> e -> e
forall a. Ord a => a -> a -> a
min e
r (e -> e -> e
forall a. Ord a => a -> a -> a
min e
g e
b) e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
i
!i :: e
i = (e
r e -> e -> e
forall a. Num a => a -> a -> a
+ e
g e -> e -> e
forall a. Num a => a -> a -> a
+ e
b) e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
3
!x :: e
x = (e
2 e -> e -> e
forall a. Num a => a -> a -> a
* e
r e -> e -> e
forall a. Num a => a -> a -> a
- e
g e -> e -> e
forall a. Num a => a -> a -> a
- e
b) e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
2.449489742783178
!y :: e
y = (e
g e -> e -> e
forall a. Num a => a -> a -> a
- e
b) e -> e -> e
forall a. Fractional a => a -> a -> a
/ e
1.4142135623730951
{-# INLINE rgb2hsi #-}