module Graphics.Image.ColorSpace.Luma (
Y(..), YA(..), Pixel(..),
ToY(..), ToYA(..)
) where
import Prelude hiding (map)
import Graphics.Image.Interface
import Data.Typeable (Typeable)
import qualified Data.Monoid as M (mappend, mempty)
import qualified Data.Colour as C
import qualified Data.Colour.Names as C
data Y = Y deriving (Eq, Enum, Typeable)
data YA = YA
| AlphaYA
deriving (Eq, Enum, Typeable)
class ColorSpace cs => ToY cs where
toPixelY :: Pixel cs Double -> Pixel Y Double
toImageY :: (Array arr cs Double, Array arr Y Double) =>
Image arr cs Double
-> Image arr Y Double
toImageY = map toPixelY
class (ToY (Opaque cs), Alpha cs) => ToYA cs where
toPixelYA :: Pixel cs Double -> Pixel YA Double
toPixelYA px = addAlpha (getAlpha px) (toPixelY (dropAlpha px))
toImageYA :: (Array arr cs Double, Array arr YA Double) =>
Image arr cs Double
-> Image arr YA Double
toImageYA = map toPixelYA
instance ColorSpace Y where
type PixelElt Y e = e
data Pixel Y e = PixelY !e deriving (Ord, Eq)
fromChannel = PixelY
fromElt = PixelY
toElt (PixelY y) = y
getPxCh (PixelY y) _ = y
chOp !f (PixelY y) = PixelY (f Y y)
pxOp !f (PixelY y) = PixelY (f y)
chApp (PixelY fy) (PixelY y) = PixelY (fy y)
pxFoldMap f (PixelY y) = f y `M.mappend` M.mempty
csColour _ = C.opaque C.darkgray
instance ColorSpace YA where
type PixelElt YA e = (e, e)
data Pixel YA e = PixelYA !e !e deriving Eq
fromChannel !e = PixelYA e e
fromElt !(g, a) = PixelYA g a
toElt (PixelYA g a) = (g, a)
getPxCh (PixelYA g _) YA = g
getPxCh (PixelYA _ a) AlphaYA = a
chOp !f (PixelYA g a) = PixelYA (f YA g) (f AlphaYA a)
pxOp !f (PixelYA g a) = PixelYA (f g) (f a)
chApp (PixelYA fy fa) (PixelYA y a) = PixelYA (fy y) (fa a)
pxFoldMap f (PixelYA y a) = f y `M.mappend` f a
csColour AlphaYA = C.opaque C.gray
csColour ch = csColour $ opaque ch
instance Alpha YA where
type Opaque YA = Y
getAlpha (PixelYA _ a) = a
addAlpha !a (PixelY g) = PixelYA g a
dropAlpha (PixelYA g _) = PixelY g
opaque YA = Y
opaque _ = error "Data.Image.ColorSpace.Luma (Alpha.opaque)"
instance Show Y where
show Y = "Luma"
instance Show YA where
show AlphaYA = "Alpha"
show ch = show $ opaque ch
instance Show e => Show (Pixel Y e) where
show (PixelY g) = "<Luma:("++show g++")>"
instance Show e => Show (Pixel YA e) where
show (PixelYA g a) = "<LumaA:("++show g++"|"++show a++")>"
instance Monad (Pixel Y) where
return = PixelY
(>>=) (PixelY y) f = f y