{-# LANGUAGE RecordWildCards #-} -- | This module contains the pixel formats supprted my babl module BABL.Format ( FFI.PixelFormat(..) , FFI.ComponentModel(..) , FFI.ComponentFormat(..) , FFI.BablFormatPtr , babl_format , babl_get_bpp , babl_format_by_str , babl_components_per_pixel ) where import qualified BABL.FFI.Format as FFI import Foreign.C.String (withCString) import Foreign.C.Types (CInt(..)) babl_components_per_pixel :: FFI.PixelFormat -> Int babl_components_per_pixel FFI.PixelFormat{..} = case pfComponents of FFI.RGB -> 3 FFI.RGBA -> 4 FFI.RaGaBaA -> 4 FFI.R'G'B' -> 3 FFI.R'G'B'A -> 4 FFI.R'aG'aB'aA -> 4 FFI.Y -> 1 FFI.YA -> 2 FFI.YaA -> 2 FFI.Y' -> 1 FFI.Y'A -> 2 FFI.Y'aA -> 2 FFI.Y'CbCr -> 3 FFI.Y'CbCrA -> 4 FFI.HSVA -> 4 FFI.HSV -> 3 FFI.CMYK -> 4 FFI.CMY -> 3 FFI.CIELab -> 3 FFI.CIELabAlpha -> 4 FFI.CIELCHab -> 3 FFI.CIELCHabAlpha -> 4 FFI.HSLA -> 4 FFI.HSL -> 3 FFI.Y'CbCr709 -> 3 FFI.Y'CbCrA709 -> 4 FFI.Cairo -> case pfType of FFI.A8 -> 1 FFI.RGB24 -> 4 FFI.ARGB32 -> 4 _ -> error "wrong type" -- | Create a 'BablFormatPtr' to pass around to other functions. babl_format :: FFI.PixelFormat -- ^ Format to be used -> IO FFI.BablFormatPtr -- ^ Pointer to specified format babl_format (FFI.PixelFormat FFI.Cairo pfType) = case pfType of FFI.A8 -> babl_format_by_str "cairo-A8" FFI.RGB24 -> babl_format_by_str "cairo-RGB24" FFI.ARGB32 -> babl_format_by_str "cairo-ARGB32" _ -> error "not a cairo format" babl_format FFI.PixelFormat{..} = babl_format_by_str (show pfComponents ++ " " ++ show pfType) -- | Build 'BablFormatPtr' by input String babl_format_by_str :: String -- ^ Input string -> IO FFI.BablFormatPtr babl_format_by_str s = return . FFI.BablFormatPtr =<< withCString s FFI.c_babl_format -- | Peek the number of bytes per pixel from a format. babl_get_bpp :: FFI.PixelFormat -- ^ Format to peek from -> IO Int babl_get_bpp form = do (FFI.BablFormatPtr ptr) <- babl_format form (CInt res) <- FFI.c_babl_get_bpp ptr return $ fromIntegral res