module Codec.BMP.BitmapInfoV5
( BitmapInfoV5 (..)
, sizeOfBitmapInfoV5
, checkBitmapInfoV5
, imageSizeFromBitmapInfoV5)
where
import Codec.BMP.Error
import Codec.BMP.BitmapInfoV4
import Data.Binary
import Data.Binary.Get
import Data.Binary.Put
data BitmapInfoV5
= BitmapInfoV5
{ dib5InfoV4 :: BitmapInfoV4
, dib5Intent :: Word32
, dib5ProfileData :: Word32
, dib5ProfileSize :: Word32
, dib5Reserved :: Word32
}
deriving (Show)
sizeOfBitmapInfoV5 :: Int
sizeOfBitmapInfoV5 = 124
instance Binary BitmapInfoV5 where
get
= do infoV4 <- get
intent <- getWord32le
pdata <- getWord32le
psize <- getWord32le
res <- getWord32le
return $ BitmapInfoV5
{ dib5InfoV4 = infoV4
, dib5Intent = intent
, dib5ProfileData = pdata
, dib5ProfileSize = psize
, dib5Reserved = res }
put header
= do put $ dib5InfoV4 header
putWord32le $ dib5Intent header
putWord32le $ dib5ProfileData header
putWord32le $ dib5ProfileSize header
putWord32le $ dib5Reserved header
checkBitmapInfoV5 :: BitmapInfoV5 -> Word32 -> Maybe Error
checkBitmapInfoV5 header expectedImageSize
= checkBitmapInfoV4 (dib5InfoV4 header) expectedImageSize
imageSizeFromBitmapInfoV5 :: BitmapInfoV5 -> Maybe Int
imageSizeFromBitmapInfoV5
= imageSizeFromBitmapInfoV4 . dib5InfoV4