-------------------------------------------------------------------------------- -- Module : Data.Bitmap.Internal -- Version : 0.0.0 -- License : BSD3 -- Copyright : (c) 2009 Balazs Komuves -- Author : Balazs Komuves -- Maintainer : bkomuves (plus) hackage (at) gmail (dot) com -- Stability : experimental -- Portability : requires FFI, CPP and ScopedTypeVariables -- Tested with : GHC 6.10.1 -------------------------------------------------------------------------------- {-# LANGUAGE CPP, ForeignFunctionInterface, ScopedTypeVariables #-} module Data.Bitmap.Internal where -------------------------------------------------------------------------------- import Control.Monad --import Data.Array.IArray import Data.Word import Foreign import Foreign.C -------------------------------------------------------------------------------- data PixelComponentType = PctWord8 | PctWord16 | PctWord32 | PctFloat deriving Show class (Num t, Storable t) => PixelComponent t where c_type :: t -> CInt nbytes :: t -> Int nbytes x = sizeOf x toFloat :: t -> Float fromFloat :: Float -> t pixelComponentType :: PixelComponent t => t -> PixelComponentType pixelComponentType t = case c_type t of 1 -> PctWord8 2 -> PctWord16 3 -> PctWord32 4 -> PctFloat instance PixelComponent Word8 where c_type _ = 1 fromFloat = floor . (*255.99999) toFloat = (*3.92156862745098e-3) . fromIntegral -- 1/255 instance PixelComponent Word16 where c_type _ = 2 fromFloat = floor . (*65535.99999) toFloat = (*1.5259021896696422e-5) . fromIntegral -- 1/65535 instance PixelComponent Word32 where c_type _ = 3 fromFloat = floor . (*4294967295.99999) toFloat = (*2.3283064370807974e-10) . fromIntegral -- 1/(2^32-1) instance PixelComponent Float where c_type _ = 4 toFloat = id fromFloat = id -- to provide better documentation type Size = (Int,Int) type Offset = (Int,Int) type NChn = Int type Padding = Int type Alignment = Int data Bitmap t = Bitmap { bitmapSize :: Size -- ^ (width,height) , bitmapNChannels :: NChn -- ^ number of channels (eg. 3 for RGB) , bitmapPtr :: ForeignPtr t -- ^ pointer to the data , bitmapRowPadding :: Padding -- ^ the padding of the rows, measured in /bytes/ , bitmapRowAlignment :: Alignment -- ^ the alignment of the rows (in bytes) } deriving Show bitmapComponentSizeInBytes :: forall t. PixelComponent t => Bitmap t -> Int bitmapComponentSizeInBytes _ = sizeOf (undefined::t) bitmapPixelSizeInBytes :: PixelComponent t => Bitmap t -> Int bitmapPixelSizeInBytes bm = bitmapNChannels bm * bitmapComponentSizeInBytes bm bitmapUnpaddedRowSizeInBytes :: forall t. PixelComponent t => Bitmap t -> Int bitmapUnpaddedRowSizeInBytes bm = w * sizeOf (undefined::t) * nchn where (w,h) = bitmapSize bm nchn = bitmapNChannels bm bitmapPaddedRowSizeInBytes :: PixelComponent t => Bitmap t -> Int bitmapPaddedRowSizeInBytes bm = bitmapUnpaddedRowSizeInBytes bm + bitmapRowPadding bm bitmapSizeInBytes :: PixelComponent t => Bitmap t -> Int bitmapSizeInBytes bm = h*x where x = bitmapPaddedRowSizeInBytes bm (_,h) = bitmapSize bm --------------------------------------------------------------------------------