-- | Adam7 interlace module PNGinterlace where import Data.Array import Utils2 as U(pieces,Split(..)) import PNG -- From the PNG specification 1.2, section 10.9 porgressive display starting_row = [0, 0, 4, 0, 2, 0, 1] starting_col = [0, 4, 0, 2, 0, 1, 0] row_increment = [8, 8, 8, 4, 4, 2, 2] col_increment = [8, 8, 4, 4, 2, 2, 1] passSize1 totalSize start incr | totalSizeif w==0 then 0 else succ w) ihdr -- no filter-type bytes are present in an empty pass adam7passesPost bs = adam7passes' id bs -- ^ Given the raw scanline data, split it into the 7 passes in preparation -- for converting scanlines bytes to per pixel data, which can then be -- deinterlaced adam7passes' adjust ihdr = zip ws . zipWith pieces ps . passes bytecounts where w = width ihdr h = height ihdr (ws,hs) = passSizes w h ps = map (adjust . pitch' ihdr) ws bytecounts = zipWith (*) ps hs passes [] bs | isEmpty bs = [] passes (n:ns) bs = case U.splitAt n bs of (bs1,bs2) -> bs1:passes ns bs2 -- http://www.libpng.org/pub/png/spec/1.2/png-1.2-pdg.html#D.Progressive-display adam7deinterlace (w,h) pixels = elems $ array ((0,0),(h-1,w-1)) (zip ixs pixels) where ixs = [(y,x)|((y0,dy),(x0,dx))<-zip (zip starting_row row_increment) (zip starting_col col_increment), y<-[y0,y0+dy..h-1], x<-[x0,x0+dx..w-1]]