module Codec.BMP.BitmapInfoV3
( BitmapInfoV3 (..)
, Compression (..)
, sizeOfBitmapInfoV3
, checkBitmapInfoV3
, imageSizeFromBitmapInfoV3)
where
import Codec.BMP.Error
import Codec.BMP.Compression
import Data.Binary
import Data.Binary.Get
import Data.Binary.Put
import Data.Int
import Debug.Trace
data BitmapInfoV3
= BitmapInfoV3
{
dib3Size :: Word32
, dib3Width :: Word32
, dib3Height :: Word32
, dib3HeightFlipped :: Bool
, dib3Planes :: Word16
, dib3BitCount :: Word16
, dib3Compression :: Compression
, dib3ImageSize :: Word32
, dib3PelsPerMeterX :: Word32
, dib3PelsPerMeterY :: Word32
, dib3ColorsUsed :: Word32
, dib3ColorsImportant :: Word32
}
deriving (Show)
sizeOfBitmapInfoV3 :: Int
sizeOfBitmapInfoV3 = 40
instance Binary BitmapInfoV3 where
get
= do size <- getWord32le
width <- getWord32le
heightW32 <- getWord32le
let heightI32 = (fromIntegral heightW32 :: Int32)
let (height, flipped)
= if heightI32 < 0
then (fromIntegral (abs heightI32), True)
else (heightW32, False)
planes <- getWord16le
bitc <- getWord16le
comp <- get
imgsize <- getWord32le
pelsX <- getWord32le
pelsY <- getWord32le
cused <- getWord32le
cimp <- getWord32le
return $ BitmapInfoV3
{ dib3Size = size
, dib3Width = width
, dib3Height = height
, dib3HeightFlipped = flipped
, dib3Planes = planes
, dib3BitCount = bitc
, dib3Compression = comp
, dib3ImageSize = imgsize
, dib3PelsPerMeterX = pelsX
, dib3PelsPerMeterY = pelsY
, dib3ColorsUsed = cused
, dib3ColorsImportant = cimp }
put header
= do putWord32le $ dib3Size header
putWord32le $ dib3Width header
putWord32le $ dib3Height header
putWord16le $ dib3Planes header
putWord16le $ dib3BitCount header
put $ dib3Compression header
putWord32le $ dib3ImageSize header
putWord32le $ dib3PelsPerMeterX header
putWord32le $ dib3PelsPerMeterY header
putWord32le $ dib3ColorsUsed header
putWord32le $ dib3ColorsImportant header
checkBitmapInfoV3 :: BitmapInfoV3 -> Word32 -> Maybe Error
checkBitmapInfoV3 header physicalBufferSize
| dib3Planes header /= 1
= Just $ ErrorUnhandledPlanesCount $ dib3Planes header
| dib3BitCount header /= 24
, dib3BitCount header /= 32
= Just $ ErrorUnhandledColorDepth $ dib3BitCount header
| headerImageSize <- dib3ImageSize header
, headerImageSize /= 0
, physicalBufferSize < headerImageSize
= Just $ ErrorImagePhysicalSizeMismatch
headerImageSize physicalBufferSize
| Just calculatedImageSize <- imageSizeFromBitmapInfoV3 header
, fromIntegral physicalBufferSize < calculatedImageSize
= trace (show header)
$ Just $ ErrorImageDataTruncated
calculatedImageSize
(fromIntegral physicalBufferSize)
| dib3Compression header /= CompressionRGB
&& dib3Compression header /= CompressionBitFields
= Just $ ErrorUnhandledCompressionMode (dib3Compression header)
| otherwise
= Nothing
imageSizeFromBitmapInfoV3 :: BitmapInfoV3 -> Maybe Int
imageSizeFromBitmapInfoV3 header
| dib3BitCount header == 32
, dib3Planes header == 1
, dib3Compression header == CompressionRGB
|| dib3Compression header == CompressionBitFields
= Just $ fromIntegral (dib3Width header * dib3Height header * 4)
| dib3BitCount header == 24
, dib3Planes header == 1
, dib3Compression header == CompressionRGB
|| dib3Compression header == CompressionBitFields
= let imageBytesPerLine = dib3Width header * 3
tailBytesPerLine = imageBytesPerLine `mod` 4
padBytesPerLine = if tailBytesPerLine > 0
then 4 tailBytesPerLine
else 0
in Just $ fromIntegral
$ dib3Height header * imageBytesPerLine + padBytesPerLine
| otherwise
= trace (show header) $ Nothing