{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Image.ColorSpace.X (
X(..), Pixel(..),
toPixelsX, toImagesX,
fromPixelsX, fromImagesX,
squashWith, squashWith2
) where
import Control.Applicative
import Data.Foldable
import Data.Typeable (Typeable)
import Foreign.Ptr
import Foreign.Storable
import Graphics.Image.Interface as I
import Prelude as P
import Graphics.Image.Utils ((.:!))
data X = X deriving (Eq, Enum, Bounded, Show, Typeable)
newtype instance Pixel X e = PixelX { getX :: e } deriving (Ord, Eq)
instance Show e => Show (Pixel X e) where
show (PixelX g) = "<X:("++show g++")>"
instance Elevator e => ColorSpace X e where
type Components X e = e
promote = PixelX
{-# INLINE promote #-}
fromComponents = PixelX
{-# INLINE fromComponents #-}
toComponents (PixelX g) = g
{-# INLINE toComponents #-}
getPxC (PixelX g) X = g
{-# INLINE getPxC #-}
setPxC (PixelX _) X g = PixelX g
{-# INLINE setPxC #-}
mapPxC f (PixelX g) = PixelX (f X g)
{-# INLINE mapPxC #-}
liftPx = fmap
{-# INLINE liftPx #-}
liftPx2 = liftA2
{-# INLINE liftPx2 #-}
foldlPx = foldl'
{-# INLINE foldlPx #-}
foldlPx2 f !z (PixelX g1) (PixelX g2) = f z g1 g2
{-# INLINE foldlPx2 #-}
instance Functor (Pixel X) where
fmap f (PixelX g) = PixelX (f g)
{-# INLINE fmap #-}
instance Applicative (Pixel X) where
pure = PixelX
{-# INLINE pure #-}
(PixelX fg) <*> (PixelX g) = PixelX (fg g)
{-# INLINE (<*>) #-}
instance Foldable (Pixel X) where
foldr f !z (PixelX g) = f g z
{-# INLINE foldr #-}
instance Monad (Pixel X) where
return = PixelX
{-# INLINE return #-}
(>>=) (PixelX g) f = f g
{-# INLINE (>>=) #-}
instance Storable e => Storable (Pixel X e) where
sizeOf _ = sizeOf (undefined :: e)
{-# INLINE sizeOf #-}
alignment _ = alignment (undefined :: e)
{-# INLINE alignment #-}
peek !p = do
q <- return $ castPtr p
g <- peek q
return (PixelX g)
{-# INLINE peek #-}
poke !p (PixelX g) = do
q <- return $ castPtr p
poke q g
{-# INLINE poke #-}
toPixelsX :: ColorSpace cs e => Pixel cs e -> [Pixel X e]
toPixelsX = foldrPx ((:) . PixelX) []
fromPixelsX :: ColorSpace cs e => [(cs, Pixel X e)] -> Pixel cs e
fromPixelsX = foldl' f (promote 0) where
f !px (c, PixelX x) = setPxC px c x
squashWith :: (Array arr cs e, Array arr X b) =>
(b -> e -> b) -> b -> Image arr cs e -> Image arr X b
squashWith f !a = I.map (PixelX . foldlPx f a) where
{-# INLINE squashWith #-}
squashWith2 :: (Array arr cs e, Array arr X b) =>
(b -> e -> e -> b) -> b -> Image arr cs e -> Image arr cs e -> Image arr X b
squashWith2 f !a = I.zipWith (PixelX .:! foldlPx2 f a) where
{-# INLINE squashWith2 #-}
toImagesX :: (Array arr cs e, Array arr X e) => Image arr cs e -> [Image arr X e]
toImagesX !img = P.map getCh (enumFrom minBound) where
getCh !ch = I.map (PixelX . (`getPxC` ch)) img
{-# INLINE getCh #-}
{-# INLINE toImagesX #-}
fromImagesX :: (Array arr X e, Array arr cs e) =>
[(cs, Image arr X e)] -> Image arr cs e
fromImagesX = fromXs 0 where
updateCh !ch !px (PixelX e) = setPxC px ch e
{-# INLINE updateCh #-}
fromXs img [] = img
fromXs img ((c, i):xs) = fromXs (I.zipWith (updateCh c) img i) xs
{-# INLINE fromXs #-}
{-# INLINE fromImagesX #-}