module Graphics.Image.ColorSpace.YCbCr (
YCbCr(..), YCbCrA(..), Pixel(..),
ToYCbCr(..), ToYCbCrA(..)
) where
import Prelude hiding (map)
import Graphics.Image.Interface
import Data.Typeable (Typeable)
import qualified Data.Monoid as M (mappend)
import qualified Data.Colour as C
import qualified Data.Colour.Names as C
data YCbCr = LumaYCbCr
| CBlueYCbCr
| CRedYCbCr
deriving (Eq, Enum, Typeable)
data YCbCrA = LumaYCbCrA
| CBlueYCbCrA
| CRedYCbCrA
| AlphaYCbCrA
deriving (Eq, Enum, Typeable)
class ColorSpace cs => ToYCbCr cs where
toPixelYCbCr :: Pixel cs Double -> Pixel YCbCr Double
toImageYCbCr :: (Array arr cs Double, Array arr YCbCr Double) =>
Image arr cs Double
-> Image arr YCbCr Double
toImageYCbCr = map toPixelYCbCr
class (ToYCbCr (Opaque cs), Alpha cs) => ToYCbCrA cs where
toPixelYCbCrA :: Pixel cs Double -> Pixel YCbCrA Double
toPixelYCbCrA px = addAlpha (getAlpha px) (toPixelYCbCr (dropAlpha px))
toImageYCbCrA :: (Array arr cs Double, Array arr YCbCrA Double) =>
Image arr cs Double
-> Image arr YCbCrA Double
toImageYCbCrA = map toPixelYCbCrA
instance ColorSpace YCbCr where
type PixelElt YCbCr e = (e, e, e)
data Pixel YCbCr e = PixelYCbCr !e !e !e deriving Eq
fromChannel !e = PixelYCbCr e e e
fromElt !(y, b, r) = PixelYCbCr y b r
toElt (PixelYCbCr y b r) = (y, b, r)
getPxCh (PixelYCbCr y _ _) LumaYCbCr = y
getPxCh (PixelYCbCr _ b _) CBlueYCbCr = b
getPxCh (PixelYCbCr _ _ r) CRedYCbCr = r
chOp !f (PixelYCbCr y b r) = PixelYCbCr (f LumaYCbCr y) (f CBlueYCbCr b) (f CRedYCbCr r)
pxOp !f (PixelYCbCr y b r) = PixelYCbCr (f y) (f b) (f r)
chApp (PixelYCbCr fy fb fr) (PixelYCbCr y b r) = PixelYCbCr (fy y) (fb b) (fr r)
pxFoldMap f (PixelYCbCr y b r) = f y `M.mappend` f b `M.mappend` f r
csColour LumaYCbCr = C.opaque C.darkgray
csColour CBlueYCbCr = C.opaque C.darkblue
csColour CRedYCbCr = C.opaque C.darkred
instance ColorSpace YCbCrA where
type PixelElt YCbCrA e = (e, e, e, e)
data Pixel YCbCrA e = PixelYCbCrA !e !e !e !e deriving Eq
fromChannel !e = PixelYCbCrA e e e e
fromElt (y, b, r, a) = PixelYCbCrA y b r a
toElt (PixelYCbCrA y b r a) = (y, b, r, a)
getPxCh (PixelYCbCrA y _ _ _) LumaYCbCrA = y
getPxCh (PixelYCbCrA _ b _ _) CBlueYCbCrA = b
getPxCh (PixelYCbCrA _ _ r _) CRedYCbCrA = r
getPxCh (PixelYCbCrA _ _ _ a) AlphaYCbCrA = a
chOp !f (PixelYCbCrA y b r a) =
PixelYCbCrA (f LumaYCbCrA y) (f CBlueYCbCrA b) (f CRedYCbCrA r) (f AlphaYCbCrA a)
pxOp !f (PixelYCbCrA y b r a) = PixelYCbCrA (f y) (f b) (f r) (f a)
chApp (PixelYCbCrA fy fb fr fa) (PixelYCbCrA y b r a) = PixelYCbCrA (fy y) (fb b) (fr r) (fa a)
pxFoldMap f (PixelYCbCrA y b r a) = f y `M.mappend` f b `M.mappend` f r `M.mappend` f a
csColour AlphaYCbCrA = C.opaque C.gray
csColour ch = csColour $ opaque ch
instance Alpha YCbCrA where
type Opaque YCbCrA = YCbCr
getAlpha (PixelYCbCrA _ _ _ a) = a
addAlpha !a (PixelYCbCr y b r) = PixelYCbCrA y b r a
dropAlpha (PixelYCbCrA y b r _) = PixelYCbCr y b r
opaque LumaYCbCrA = LumaYCbCr
opaque CBlueYCbCrA = CBlueYCbCr
opaque CRedYCbCrA = CRedYCbCr
opaque AlphaYCbCrA = error "Data.Image.ColorSpace.YCbCr (Alpha.opaque)"
instance Show YCbCr where
show LumaYCbCr = "Luma"
show CBlueYCbCr = "Blue Chroma"
show CRedYCbCr = "Red Chroma"
instance Show YCbCrA where
show AlphaYCbCrA = "Alpha"
show ch = show $ opaque ch
instance Show e => Show (Pixel YCbCr e) where
show (PixelYCbCr y b r) = "<YCbCr:("++show y++"|"++show b++"|"++show r++")>"
instance Show e => Show (Pixel YCbCrA e) where
show (PixelYCbCrA y b r a) = "<YCbCrA:("++show y++"|"++show b++"|"++show r++"|"++show a++")>"