-- | PNG Adaptive filter types, -- {-# LANGUAGE FlexibleContexts #-} module PNGfilter where import Data.List(zipWith4) import Byte(byte) import Utils2 as U import PNG type Scanline = [Byte] --apply_filter :: IHDR -> [Scanline] -> [Scanline] apply_filter ihdr = map filtr where -- See section 9.6 Filter selection filtr = if colorType ihdr==IndexedColor || bitDepth ihdr<8 then none else sub none raw = single (byte None)<>raw sub raw = single (byte Sub)<>U.zipWith subtract left raw where left = U.replicate b 0<>raw b = (bpp ihdr+7) `quot` 8 -- bytes per pixel, rounded up undo_filter :: Int -> [Scanline] -> [Scanline] undo_filter b scanlines = rawlines where rawlines = U.zipWith unfilter uplines scanlines uplines = repeat 0:rawlines unfilter prior [] = [] -- can happen in small interlaced PNGs unfilter prior (b0:bs) | b0>4 = error $ "Bad filter type: "++show b0 -- parser should check this | otherwise = case toEnum (fromEnum b0) of None -> bs Up -> U.zipWith (+) bs prior Sub -> raw where raw = U.zipWith (+) bs left left = U.replicate b 0++raw Average -> raw where raw = zipWith3 average bs left prior left = U.replicate b 0++raw average b l p = b+toEnum((fromEnum l+fromEnum p) `quot` 2) Paeth -> raw where raw = zipWith4 paeth bs left prior upleft left = U.replicate b 0++raw upleft = U.replicate b 0++prior paeth b l p ul = b+paeth' l p ul paeth' a b c = toEnum (paethPredictor (fromEnum a) (fromEnum b) (fromEnum c)) -- | Paeth predictor -- paethPredictor a b c = -- a = left, b = above, c = upper left -- return nearest of a,b,c, -- breaking ties in order a,b,c. if pa <= pb && pa <= pc then a else if pb <= pc then b else c where p = a + b - c -- initial estimate pa = abs(p - a) -- distances to a, b, c pb = abs(p - b) pc = abs(p - c)