-- http://www.w3.org/TR/PNG/ -- Based on http://mainisusuallyafunction.blogspot.se/2012/04/minimal-encoder-for-uncompressed-pngs.html module PNGchunks(PNGstream(..),Chunk(..),png_chunk,bytes,png_signature,crc32) where import Data.Bits hiding (bit) import Data.Word(Word32) import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy.Char8 as CS import Byte(ord) import ByteStream(Bytes(..),be32) png_signature = CS.pack "\x89PNG\r\n\x1a\n" data PNGstream = PNGstream [Chunk] deriving Show instance Bytes PNGstream where bytes (PNGstream chunks) = png_signature `BS.append` bytes chunks data Chunk = Chunk {len::Word32,typ::FourCC,bs::BS.ByteString,crc::Word32} deriving (Eq,Show) type FourCC = String -- ^ Four ASCII characters instance Bytes Chunk where bytes (Chunk len ty bs crc) = BS.concat [be32 len,CS.pack ty,bs,be32 crc] png_chunk ty bytes | n<=maxInt32 = Chunk n ty bytes (crc32 (ty'++BS.unpack bytes)) where n = fromIntegral (BS.length bytes) ty' = BS.unpack $ CS.pack ty maxInt32 = 0x7fffffff crc32 bs = complement $ bytes (complement 0) bs where bytes crc [] = crc bytes crc (b:bs) | crc>=0 = bytes (byte crc b) bs -- strictness trick byte a x = bit . bit . bit . bit . bit . bit . bit . bit $ xor a (ord x) bit c = if odd c then k `xor` shiftR c 1 else shiftR c 1 --k = -306674912 k = 0xedb88320