module Codec.BMP.Pack
( packRGBA32ToBMP
, packRGBA32ToBMP24
, packRGBA32ToBMP32)
where
import Codec.BMP.Base
import Codec.BMP.BitmapInfo
import Codec.BMP.BitmapInfoV3
import Codec.BMP.FileHeader
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.Storable
import System.IO.Unsafe
import Data.Word
import Data.Maybe
import Data.ByteString as BS
import Data.ByteString.Unsafe as BS
import Prelude as P
packRGBA32ToBMP
:: Int
-> Int
-> ByteString
-> BMP
packRGBA32ToBMP = packRGBA32ToBMP32
packRGBA32ToBMP32
:: Int
-> Int
-> ByteString
-> BMP
packRGBA32ToBMP32 width height str
| width < 0
= error "Codec.BMP: Negative width field."
| height < 0
= error "Codec.BMP: Negative height field."
| height * width * 4 /= BS.length str
= error "Codec.BMP: Image dimensions don't match input data."
| otherwise
= let imageData = packRGBA32ToBGRA32 width height str
in packDataToBMP 32 width height imageData
packRGBA32ToBMP24
:: Int
-> Int
-> ByteString
-> BMP
packRGBA32ToBMP24 width height str
| width < 0
= error "Codec.BMP: Negative width field."
| height < 0
= error "Codec.BMP: Negative height field."
| height * width * 4 /= BS.length str
= error "Codec.BMP: Image dimensions don't match input data."
| otherwise
= let imageData = packRGBA32ToBGR24 width height str
in packDataToBMP 24 width height imageData
packDataToBMP
:: Int
-> Int
-> Int
-> ByteString
-> BMP
packDataToBMP bits width height imageData
= let fileHeader
= FileHeader
{ fileHeaderType = bmpMagic
, fileHeaderFileSize
= fromIntegral
$ sizeOfFileHeader + sizeOfBitmapInfoV3
+ BS.length imageData
, fileHeaderReserved1 = 0
, fileHeaderReserved2 = 0
, fileHeaderOffset
= fromIntegral (sizeOfFileHeader + sizeOfBitmapInfoV3)}
bitmapInfoV3
= BitmapInfoV3
{ dib3Size = fromIntegral sizeOfBitmapInfoV3
, dib3Width = fromIntegral width
, dib3Height = fromIntegral height
, dib3HeightFlipped = False
, dib3Planes = 1
, dib3BitCount = fromIntegral bits
, dib3Compression = CompressionRGB
, dib3ImageSize = fromIntegral $ BS.length imageData
, dib3PelsPerMeterX = 2834
, dib3PelsPerMeterY = 2834
, dib3ColorsUsed = 0
, dib3ColorsImportant = 0 }
errs = catMaybes
[ checkFileHeader fileHeader
, checkBitmapInfoV3 bitmapInfoV3
(fromIntegral $ BS.length imageData)]
in case errs of
[] -> BMP
{ bmpFileHeader = fileHeader
, bmpBitmapInfo = InfoV3 bitmapInfoV3
, bmpRawImageData = imageData }
_ -> error $ "Codec.BMP: Constructed BMP file has errors, sorry."
++ show errs
packRGBA32ToBGR24
:: Int
-> Int
-> ByteString
-> ByteString
packRGBA32ToBGR24 width height str
| height * width * 4 /= BS.length str
= error "Codec.BMP: Image dimensions don't match input data."
| otherwise
= let padPerLine
= case (width * 3) `mod` 4 of
0 -> 0
x -> 4 x
sizeDest = height * (width * 3 + padPerLine)
in unsafePerformIO
$ allocaBytes sizeDest $ \bufDest ->
BS.unsafeUseAsCString str $ \bufSrc ->
do packRGBA32ToBGR24' width height padPerLine
(castPtr bufSrc) (castPtr bufDest)
bs <- packCStringLen (bufDest, sizeDest)
return bs
packRGBA32ToBGR24' width height pad ptrSrc ptrDest
= go 0 0 0 0
where
go posX posY oSrc oDest
| posX == width
= do mapM_ (\n -> pokeByteOff ptrDest (oDest + n) (0 :: Word8))
$ P.take pad [0 .. ]
go 0 (posY + 1) oSrc (oDest + pad)
| posY == height
= return ()
| otherwise
= do red :: Word8 <- peekByteOff ptrSrc (oSrc + 0)
green :: Word8 <- peekByteOff ptrSrc (oSrc + 1)
blue :: Word8 <- peekByteOff ptrSrc (oSrc + 2)
pokeByteOff ptrDest (oDest + 0) blue
pokeByteOff ptrDest (oDest + 1) green
pokeByteOff ptrDest (oDest + 2) red
go (posX + 1) posY (oSrc + 4) (oDest + 3)
packRGBA32ToBGRA32
:: Int
-> Int
-> ByteString
-> ByteString
packRGBA32ToBGRA32 width height str
| height * width * 4 /= BS.length str
= error "Codec.BMP: Image dimensions don't match input data."
| otherwise
= let sizeDest = height * (width * 4)
in unsafePerformIO
$ allocaBytes sizeDest $ \bufDest ->
BS.unsafeUseAsCString str $ \bufSrc ->
do packRGBA32ToBGRA32' width height
(castPtr bufSrc) (castPtr bufDest)
bs <- packCStringLen (bufDest, sizeDest)
return bs
packRGBA32ToBGRA32' width height ptrSrc ptrDest
= go 0 0 0 0
where
go posX posY oSrc oDest
| posX == width
= do go 0 (posY + 1) oSrc oDest
| posY == height
= return ()
| otherwise
= do red :: Word8 <- peekByteOff ptrSrc (oSrc + 0)
green :: Word8 <- peekByteOff ptrSrc (oSrc + 1)
blue :: Word8 <- peekByteOff ptrSrc (oSrc + 2)
alpha :: Word8 <- peekByteOff ptrSrc (oSrc + 3)
pokeByteOff ptrDest (oDest + 0) blue
pokeByteOff ptrDest (oDest + 1) green
pokeByteOff ptrDest (oDest + 2) red
pokeByteOff ptrDest (oDest + 3) alpha
go (posX + 1) posY (oSrc + 4) (oDest + 4)