-- | Portable Network Graphics {-# LANGUAGE DeriveTraversable #-} module PNG(module PNG,RGB(..),Byte) where import Data.Foldable import Data.Traversable import RGB -- ** Main types and critical chunks data PNG idata = PNG { ihdr::IHDR, -- ^ Critical IHDR chunk plte::PLTE, -- ^ Critical PLTE chunk bkgd::BKGD, -- ^ Ancillary bKGD chunk trns::TRNS, -- ^ Ancillary tRNS chunk idata::idata -- ^ Critical IDAT chunk } deriving (Show,Functor,Foldable,Traversable) data IHDR = IHDR { width,height::Int, -- [1..2^31-1] bitDepth::Depth, colorType::ColorType, compressionMethod::CompressionMethod, filterMethod::FilterMethod, interlaceMethod::InterlaceMethod } deriving Show newtype PLTE = PLTE [RGB8] deriving Show -- 1 to 256 entries noPLTE = PLTE [] -- ** Auxiliary types data ColorType = GreyScale -- 0 | Truecolor -- 2 | IndexedColor -- 3 | GreyScaleWithAlpha -- 4 | TruecolorWithAlpha -- 6 deriving (Eq,Show) data CompressionMethod = ZlibDeflate deriving (Eq,Enum,Show) -- 0 data FilterMethod = Adaptive deriving (Eq,Enum,Show) -- 0 data InterlaceMethod = NoInterlace | Adam7 deriving (Eq,Enum,Show) -- 0, 1 data FilterType = None | Sub | Up | Average | Paeth deriving (Eq,Enum,Show) type Depth = Byte -- ^ 1, 2, 4, 8 or 16, restricted depending on ColorType -------------------------------------------------------------------------------- -- ** Convenience functions ihdr' d t w h = IHDR w h d t ZlibDeflate Adaptive NoInterlace rgb8ihdr = ihdr' 8 Truecolor grey8ihdr = ihdr' 8 GreyScale bitmapIhdr = ihdr' 1 GreyScale indexedIhdr = ihdr' 8 IndexedColor -- | A Truecolor PNG, 3 bytes per pixel rgbPNG w h = PNG (rgb8ihdr w h) noPLTE noBKGD noTRNS greyPNG w h = PNG (grey8ihdr w h) noPLTE noBKGD noTRNS -- ^ A GreyScale PNG, 1 byte per pixel bitmapPNG w h = PNG (bitmapIhdr w h) noPLTE noBKGD noTRNS -- ^ A black & white PNG, 1 bit per pixel indexedPNG w h cm = PNG (indexedIhdr w h) (PLTE cm) noBKGD noTRNS -- | Bits per pixel bpp ihdr = fromEnum (bitDepth ihdr)*channels (colorType ihdr) -- | Number of values per pixel channels colorType = case colorType of GreyScale -> 1 Truecolor -> 3 IndexedColor -> 1 GreyScaleWithAlpha -> 2 TruecolorWithAlpha -> 4 -- | Number of bytes per scanline pitch ihdr = pitch' ihdr (width ihdr) pitch' ihdr w = (bpp ihdr * w + 7) `quot` 8 -------------------------------------------------------------------------------- -- ** Ancillary chunks -- | pHYs ancillary chunk data PHYs = PHYs {ppu_x,ppu_y::Int, unit::Byte} deriving Show -- | bKGD ancillary chunk data BKGD = NoBg -- ^ Not present | IxBg Byte -- ^ For IndexedColor images (type 3) | GreyBg Short -- ^ For Grey images (type 0 & 4) | TruecolorBg RGB16 -- ^ For Truecolor images (type 2 & 6) deriving (Eq,Show) noBKGD = NoBg -- | tRNS ancillary chunk data TRNS = IxTrans [Byte] -- ^ For IndexedColor images (type 3) | GreyTrans Short -- ^ For Grey images (type 0) | TruecolorTrans RGB16 -- ^ For Truecolor iamges (type 2) deriving (Eq,Show) noTRNS = IxTrans []