PNGReader.st
author Claus Gittinger <cg@exept.de>
Mon, 22 Dec 2014 13:00:09 +0100
changeset 3437 4e1cf7b6b492
parent 3384 0761606da988
child 3461 eb5a53c6b5b2
permissions -rw-r--r--
class: PNGReader comment/format in: #documentation changed: #copyPixels:at:by: #copyPixelsRGBA:at:by: fixed deinterlace for rgba images.

"
 COPYRIGHT (c) 1996 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libview2' }"

ImageReader subclass:#PNGReader
	instanceVariableNames:'colorType bitsPerChannel depth compressionMethod filterMethod
		interlaceMode bytesPerScanline globalDataChunk thisScanline
		prevScanline'
	classVariableNames:'Verbose'
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

!PNGReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    This class will provide methods for loading and saving PNG pictures.
    It is currenty unfinished (interlaced image support is missing resp. being developed as we encounter more formats).
    In the meantime, use a pngtoXXX converter for interlaced images, and read XXX.

    [caveats:]
        writer ignores any mask (for now).
        writer only generates unfiltered rows or interlace data
        
    [See also:]
        Image Form Icon
        BlitImageReader FaceReader GIFReader JPEGReader PBMReader PCXReader 
        ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
        XBMReader XPMReader XWDReader 

    [author:]
        Claus Gittinger
"
!

examples
"
    PNGReader fromFile:'/home/cg/AudioExplorer_51_files/use_small.png'
    PNGReader fromFile:'\\Exeptn\tmp\images\expeccoScreenshot4020_5526507.png'

    PNGReader fromFile:'C:\Users\cg\Desktop\croquet\cobalt-base-current-build-20090210\cobalt-base-current-build-20090210\content\models\textures\checkerboard.png'
    PNGReader fromFile:'C:\Dokumente und Einstellungen\cg\Desktop\misc\PNGs\Delete.png'
    PNGReader fromFile:'\\exeptn\unsaved\pd_stuff\PNGs\Delete.png'
    PNGReader fromFile:'\\exeptn\unsaved\pd_stuff\PNGs\Down.png'


    |img img2 outStream png|

    img := ToolbarIconLibrary error32x32Icon.
    outStream := WriteStream on:(ByteArray new:100).
    PNGReader save:img onStream:outStream.
    png := outStream contents.
    img2 := PNGReader fromStream:(png readStream).
    self assert:(img bits = img2 bits).
    img inspect.
    img2 inspect.
"
! !

!PNGReader class methodsFor:'initialization'!

initialize
    "install myself in the Image classes fileFormat table for the `.png' extension."

    MIMETypes defineImageType:'image/png'  suffix:'png' reader:self.
    "/ backward compatibility from times when png was not yet so common...
    MIMETypes defineImageType:'image/x-png' suffix:nil reader:self.
! !

!PNGReader class methodsFor:'queries'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     Any image is supported."

    ^ true
! !

!PNGReader class methodsFor:'testing'!

isValidImageFile:aFileName
    "return true, if aFileName contains a PNG image"

    |inStream magic|

    inStream := self streamReadingFile:aFileName.
    inStream isNil ifTrue:[^ false].

    inStream binary.

    magic := ByteArray new:8.
    inStream nextBytes:8 into:magic.
    inStream close.

    ^ (magic = #[137 80 78 71 13 10 26 10])

    "
     self isValidImageFile:'/home/cg/AudioExplorer_51_files/use_small.png'
     self isValidImageFile:'C:\Users\cg\Desktop\croquet\cobalt-base-current-build-20090210\cobalt-base-current-build-20090210\content\models\textures\checkerboard.png'
     self isValidImageFile:'C:\Dokumente und Einstellungen\cg\Desktop\misc\PNGs\Delete.png'
    "

    "Modified: 21.6.1996 / 20:38:46 / cg"
! !

!PNGReader methodsFor:'private-chunks'!

doPass: pass
    "Certain interlace passes are skipped with certain small image dimensions"

    pass = 1 ifTrue: [ ^ true ].
    ((width = 1) and: [height = 1]) ifTrue: [ ^ false ].
    pass = 2 ifTrue: [ ^ width >= 5 ].
    pass = 3 ifTrue: [ ^ height >= 5 ].
    pass = 4 ifTrue: [ ^ (width >=3 ) or: [height >= 5] ].
    pass = 5 ifTrue: [ ^ height >=3 ].
    pass = 6 ifTrue: [ ^ width >=2 ].
    pass = 7 ifTrue: [ ^ height >=2 ].

    self error:'invalid argument'.
    ^ true
!

processBKGDChunkLen:len
    inStream skip:len.
    ^ true

    "Created: 21.6.1996 / 21:15:49 / cg"
!

processCHRMChunkLen:len
    "cHRM Primary chromaticities chunk - currently unhandled"

    |whitePointX whitePointY redX redY greenX greenY blueX blueY|

    whitePointX := (inStream nextLongMSB:true) / 100000.0.
    whitePointY := (inStream nextLongMSB:true) / 100000.0.
    redX := (inStream nextLongMSB:true) / 100000.0.
    redY := (inStream nextLongMSB:true) / 100000.0.
    greenX := (inStream nextLongMSB:true) / 100000.0.
    greenY := (inStream nextLongMSB:true) / 100000.0.
    blueX := (inStream nextLongMSB:true) / 100000.0.
    blueY := (inStream nextLongMSB:true) / 100000.0.

    Verbose == true ifTrue:[
        'PNGReader: CHRM chunk ignored:' infoPrintCR.
        'PNGReader:   whitePointX:' infoPrint. whitePointX infoPrintCR.
        'PNGReader:   whitePointY:' infoPrint. whitePointX infoPrintCR.
        'PNGReader:   redX:' infoPrint. redX infoPrintCR.
        'PNGReader:   redY:' infoPrint. redY infoPrintCR.
        'PNGReader:   greenX:' infoPrint. greenX infoPrintCR.
        'PNGReader:   greenY:' infoPrint. greenY infoPrintCR.
        'PNGReader:   blueX:' infoPrint. blueX infoPrintCR.
        'PNGReader:   blueY:' infoPrint. blueY infoPrintCR.
    ].
    ^ true
!

processChunk:type len:len
    |chunk|

    type = 'IDAT' ifTrue:[
        "---since the compressed data can span multiple
        chunks, stitch them all together first. later,
        if memory is an issue, we need to figure out how
        to do this on the fly---"
        chunk := inStream next:len.
        globalDataChunk := globalDataChunk isNil 
                                ifTrue: [chunk] 
                                ifFalse:[globalDataChunk,chunk].
        ^ true
"/        ^ self processIDATChunkLen:len
    ].

    type = 'gAMA' ifTrue:[^ self processGAMAChunkLen:len].
    type = 'sBIT' ifTrue:[^ self processSBITChunkLen:len].
    type = 'tEXt' ifTrue:[^ self processTEXTChunkLen:len].
    type = 'tIME' ifTrue:[^ self processTIMEChunkLen:len].
    type = 'bKGD' ifTrue:[^ self processBKGDChunkLen:len].
    type = 'zTXt' ifTrue:[^ self processZTXTChunkLen:len].
    type = 'PLTE' ifTrue:[^ self processPLTEChunkLen:len].

    type = 'pHYs' ifTrue:[^ self processPHYSChunkLen:len].
    type = 'cHRM' ifTrue:[^ self processCHRMChunkLen:len].
    type = 'tRNS' ifTrue:[^ self processTRNSChunkLen:len].
    type = 'IHDR' ifTrue:[^ self processIHDRChunkLen:len].

    ('PNGReader: unrecognized chunk: ' , type , ' ignored.') infoPrintCR.

    inStream skip:len.
    ^ true.

    "Created: 21.6.1996 / 21:10:37 / cg"
    "Modified: 21.6.1996 / 21:22:37 / cg"
!

processGAMAChunkLen:len
    inStream skip:len.
    ^ true

    "Created: 21.6.1996 / 21:10:52 / cg"
!

processGlobalIDATChunk
    interlaceMode == 0 ifTrue: [
        ^ self processNonInterlacedGlobalDATA
    ]. 
    ^ self processInterlacedGlobalDATA
!

processIDATChunkLen:len
    interlaceMode == 0 ifTrue: [
        ^ self processNonInterlacedDATA:len
    ]. 
    ^ self processInterlacedDATA:len
!

processInterlacedDATA:len
    inStream skip:len.
    ^ true
!

processInterlacedGlobalDATA
    "adam7 interlace method"

    | zlibReader filter bytesPerPass startingCol colIncrement rowIncrement 
      startingRow cx sc temp "filtersSeen" bitsPerPixel cy|

    interlaceMode == 1 ifFalse: [
        self error:'unsupported interlaced mode'.
        ^ self
    ].

    "/ filtersSeen := Set new.

    startingCol := #(0 4 0 2 0 1 0 ).
    startingRow := #(0 0 4 0 2 0 1 ).
    colIncrement := #(8 8 4 4 2 2 1 ).
    rowIncrement := #(8 8 8 4 4 2 2 ).

    zlibReader := ZipStream readOpenAsZipStreamOn:(globalDataChunk readStream) suppressHeaderAndChecksum:false.
    zlibReader binary.
    bytesPerScanline := self bytesPerRow.
    bitsPerPixel := self bitsPerPixel.

    1 to: 7 do: [:pass |
        (self doPass: pass) ifTrue:[
            cx := colIncrement at: pass.
            sc := startingCol at: pass.
            cy := rowIncrement at: pass.
            bytesPerPass := width - sc + cx - 1 // cx * bitsPerPixel + 7 // 8.
            prevScanline := ByteArray new: bytesPerPass.
            thisScanline := ByteArray new: bytesPerScanline.
            (startingRow at: pass) to: height - 1 by: cy do: [:y |
                filter := zlibReader nextByte.
                "/ filtersSeen add: filter.
                (filter isNil or: [(filter between: 0 and: 4) not])
                    ifTrue: [^ self].
                zlibReader next: bytesPerPass into: thisScanline startingAt: 1.
                filter ~~ 0 ifTrue:[ self filterScanline: filter count: bytesPerPass ].
                self copyPixels:y at:sc by:cx.
                temp := prevScanline.
                prevScanline := thisScanline.
                thisScanline := temp.
            ]
        ]
    ].
    zlibReader atEnd ifFalse:[self error:'Unexpected data'].

    "Modified: / 03-05-2011 / 12:03:33 / cg"
!

processNonInterlacedDATA:len
    self halt:'not used'
"/
"/    | zlibReader filter temp prevScanline thisScanline bytesPerScanline filtersSeen|
"/
"/    zlibReader := ZipStream readOpenAsZipStreamOn:inStream suppressHeaderAndChecksum:false. 
"/    "/ zlibReader := ZLibReadStream on:inStream from: 1 to:len.
"/
"/    prevScanline := ByteArray new: self bytesPerRow.
"/    thisScanline := ByteArray new: self bytesPerRow.
"/    0 to: height - 1 do:[:index | 
"/            filter := (zlibReader next: 1) first.
"/            filtersSeen add: filter.
"/            (filter isNil or: [(filter between: 0 and: 4) not]) ifTrue: [^self].
"/            thisScanline := zlibReader next: bytesPerScanline into: thisScanline startingAt: 1.
"/            self filterScanline: filter count: bytesPerScanline.
"/            self copyPixels: index.
"/            temp := prevScanline.
"/            prevScanline := thisScanline.
"/            thisScanline := temp
"/    ]
!

processNonInterlacedGlobalDATA
    | "data n" zlibReader filter temp bytesPerScanline "filtersSeen" i|

    "/ filtersSeen := Set new.

"/    data := ByteArray new:(self bytesPerRow * height)+1000.
"/    n := ZipStream uncompress: globalDataChunk into: data.
"/    self halt.

    zlibReader := ZipStream readOpenAsZipStreamOn:(globalDataChunk readStream) suppressHeaderAndChecksum:false.
    zlibReader binary.
    bytesPerScanline := self bytesPerRow.

    prevScanline := ByteArray new: bytesPerScanline.
    thisScanline := ByteArray new: bytesPerScanline.
    0 to: height - 1 do:[:y | 
        filter := zlibReader nextByte.
        "/ filtersSeen add: filter.
        (filter notNil and: [filter between: 0 and: 4]) ifFalse: [
            'PNGReader: unsupported filter' infoPrintCR.
            ^ self
        ].
        zlibReader next: bytesPerScanline into: thisScanline startingAt: 1.
        filter ~~ 0 ifTrue:[ self filterScanline: filter count: bytesPerScanline ].

        i := y * bytesPerScanline.
        data replaceFrom:i+1 to:(i+bytesPerScanline) with:thisScanline startingAt:1.

        temp := prevScanline.
        prevScanline := thisScanline.
        thisScanline := temp
    ]
!

processPHYSChunkLen:len
    "physical pixel chunk - currently unhandled"

    |pixelPerUnitX pixelPerUnitY unit|

    pixelPerUnitX := inStream nextLongMSB:true.  
    pixelPerUnitY := inStream nextLongMSB:true.
    unit := inStream nextByte.

    Verbose == true ifTrue:[
        'PNGReader: PHYS chunk ignored:' infoPrintCR.
        'PNGReader:   ppuX:' infoPrint. pixelPerUnitX infoPrintCR.
        'PNGReader:   ppuY:' infoPrint. pixelPerUnitY infoPrintCR.
        'PNGReader:   unit:' infoPrint. unit infoPrintCR.
    ].

    ^ true
!

processPLTEChunkLen:len
    "read a color palette"

    |n "{ Class: SmallInteger }"
     redBytes greenBytes blueBytes|

    (len \\ 3) ~~ 0 ifTrue:[
        'PNGReader: invalid size of PLTE chunk' infoPrintCR.
        ^ false
    ].
    n := len // 3.
    redBytes := ByteArray new:n.
    greenBytes := ByteArray new:n.
    blueBytes := ByteArray new:n.

    1 to:n do:[:i |
        redBytes at:i put:(inStream nextByte).
        greenBytes at:i put:(inStream nextByte).
        blueBytes at:i put:(inStream nextByte)
    ].

    colorMap := MappedPalette 
                    redVector:redBytes 
                    greenVector:greenBytes 
                    blueVector:blueBytes.

    ^ true

    "Created: 21.6.1996 / 21:22:28 / cg"
    "Modified: 21.6.1996 / 21:43:01 / cg"
!

processSBITChunkLen:len
    inStream skip:len.
    ^ true

    "Created: 21.6.1996 / 21:13:09 / cg"
!

processTEXTChunkLen:len
    inStream skip:len.
    ^ true

    "Modified: 21.6.1996 / 21:15:27 / cg"
!

processTIMEChunkLen:len
    inStream skip:len.
    ^ true

    "Created: 21.6.1996 / 21:15:43 / cg"
    "Modified: 21.6.1996 / 21:20:42 / cg"
!

processTRNSChunkLen:len
    inStream skip:len.
    ^ true
!

processZTXTChunkLen:len
    inStream skip:len.
    ^ true

    "Created: 21.6.1996 / 21:15:58 / cg"
! !

!PNGReader methodsFor:'private-filtering'!

filterAverage:count 
    "Use the average of the pixel to the left and the pixel above as a predictor"
    
    |delta|

    delta := self bitsPerPixel // 8 max:1.
    1 to:delta do:[:i | 
        thisScanline at:i put:((thisScanline at:i) + ((prevScanline at:i) // 2) bitAnd:255)
    ].
    delta + 1 to:count do:[:i | 
        thisScanline at:i put:((thisScanline at:i) + (((prevScanline at:i) + (thisScanline at:i - delta)) // 2) bitAnd:255)
    ]

    "Modified: / 03-05-2011 / 12:14:01 / cg"
!

filterHorizontal:count
    "use the pixel to the left as a predictor"

    |delta|

    delta := self bitsPerPixel // 8 max:1.
    delta+1 to:count do:[:i|
        thisScanline at:i put:(((thisScanline at:i)+ (thisScanline at:i-delta)) bitAnd:255) 
    ]
!

filterNone: count
    "/ no filter - scanline is as is

    "Modified: / 03-05-2011 / 12:14:20 / cg"
!

filterPaeth:count 
    "Select one of (the pixel to the left, the pixel above and the pixel to above left) to
     predict the value of this pixel"
    
    |delta|

    delta := self bitsPerPixel // 8 max:1.
    1 to:delta do:[:i | 
        thisScanline 
            at:i
            put:(((thisScanline at:i) + (prevScanline at:i)) bitAnd:255)
    ].
    delta + 1 to:count do:[:i | 
        thisScanline 
            at:i
            put:(((thisScanline at:i) + (self 
                            paethPredictLeft:(thisScanline at:i - delta)
                            above:(prevScanline at:i)
                            aboveLeft:(prevScanline at:i - delta))) 
                    bitAnd:255)
    ]

    "Modified: / 03-05-2011 / 12:14:43 / cg"
!

filterScanline:filterType count:count
    self 
        perform:(#(filterNone: filterHorizontal: filterVertical: filterAverage: filterPaeth:) at:filterType+1)
        with:count

    "Modified: / 03-05-2011 / 12:13:31 / cg"
!

filterVertical:count 
    "Use the pixel above as a predictor"
    
    1 to:count do:[:i | 
        thisScanline 
            at:i
            put:(((thisScanline at:i) + (prevScanline at:i)) bitAnd:255)
    ]

    "Modified: / 03-05-2011 / 12:14:34 / cg"
!

paethPredictLeft: a above: b aboveLeft: c
    "Predicts the value of a pixel based on nearby pixels, based on Paeth (GG II, 1991)"

    | pa pb pc |

    pa := b > c ifTrue: [b - c] ifFalse: [c - b].
    pb := a > c ifTrue: [a - c] ifFalse: [c - a].
    pc := a + b - c - c.
    pc < 0 ifTrue: [
        pc := pc * -1
    ].
    ((pa <= pb) and: [pa <= pc]) ifTrue: [^ a].
    (pb <= pc) ifTrue: [^ b].
    ^ c
! !

!PNGReader methodsFor:'private-pixel copy'!

copyPixels:y at:startX by:incX 
    "Handle interlaced pixels of supported colorTypes"
    
    |s|

    s := #( #copyPixelsGray:at:by:
             nil
             #copyPixelsRGB:at:by: 
             #copyPixelsIndexed:at:by:
             #copyPixelsGrayAlpha:at:by: 
             nil 
             #copyPixelsRGBA:at:by: 
        ) at:colorType + 1.
    self perform:s with:y with:startX with:incX

    "Modified: / 03-05-2011 / 12:02:45 / cg"
!

copyPixelsRGBA:y at:startX by:incX 
    "Handle interlaced pixels of supported colorTypes.
     Untested code - please verify"

    |srcIndex nPixels dstIndex dstInc|

    srcIndex := 1.
    dstIndex := (y * bytesPerScanline) + (startX * 4) + 1.
    dstInc := incX * 4.

    nPixels := thisScanline size.
    [srcIndex < nPixels] whileTrue:[
        data replaceFrom:dstIndex to:dstIndex+3 with:thisScanline startingAt:srcIndex.
        srcIndex := srcIndex + 4.
        dstIndex := dstIndex + dstInc
    ].
! !

!PNGReader methodsFor:'private-reading'!

getChunk
    |len type crc|

    inStream atEnd ifTrue:[^ false].

    len := inStream nextLongMSB:true.
    type := String new:4.
    (inStream nextBytes:4 into:type) ~~ 4 ifTrue:[^ false].

    Verbose == true ifTrue:[
        'len: ' infoPrint. len infoPrint. ' type: ' infoPrint. type infoPrintCR.
    ].

    type = 'IEND' ifTrue:[^ false].

    (self processChunk:type len:len) ifFalse:[^ false].

    crc := inStream nextLongMSB:true.  "/ ignored - for now
    ^ true

    "Created: 21.6.1996 / 21:09:36 / cg"
    "Modified: 21.6.1996 / 21:20:26 / cg"
!

getIHDRChunk
    |len type crc|

    len := inStream nextLongMSB:true.

    type := String new:4.
    inStream nextBytes:4 into:type.

    type = 'IHDR' ifFalse:[self halt:'expected IHDR magic'. ^ false].
    len == 13 ifFalse:[self halt:'unexpected IHDR length'. ^ false].

    width := inStream nextLongMSB:true.        
    height := inStream nextLongMSB:true.        

    (width <= 0 or:[height <= 0]) ifTrue:[
        'PNGReader: invalid dimension(s)' infoPrintCR.
        ^ false.
    ].
    self reportDimension.

    depth := inStream nextByte.            "/ bits-per-channel
    colorType := inStream nextByte.

    compressionMethod := inStream nextByte.
    filterMethod := inStream nextByte.
    interlaceMode := inStream nextByte.

    Verbose == true ifTrue:[
        'PNGReader: IHDR:' infoPrintCR.
        'PNGReader:   width: ' infoPrint. width infoPrintCR.
        'PNGReader:   height: ' infoPrint. height infoPrintCR.
        'PNGReader:   depth: ' infoPrint. depth infoPrintCR.
        'PNGReader:   colorType: ' infoPrint. colorType infoPrintCR.
        'PNGReader:   compressionMethod: ' infoPrint. compressionMethod infoPrintCR.
        'PNGReader:   filterMethod: ' infoPrint. filterMethod infoPrintCR.
        'PNGReader:   interlaceMode: ' infoPrint. interlaceMode infoPrintCR.
    ].

    crc := inStream nextLongMSB:true.
    ^ true

    "Modified: 21.6.1996 / 21:38:35 / cg"
!

setColorType:colorType
    colorType == 0 ifTrue:[
        photometric := #blackIs0.
        samplesPerPixel := 1.
        bitsPerSample := Array with:depth.
        ^ true.
    ].

    colorType == 2 ifTrue:[
        depth < 8 ifTrue:[
            'PNGReader: invalid colorType/depth combination' infoPrintCR.
            ^ false.
        ].
        photometric := #rgb.
        samplesPerPixel := 3.
        bitsPerSample := Array with:depth with:depth with:depth.
        ^ true.
    ].

    colorType == 3 ifTrue:[
        depth == 16 ifTrue:[
            'PNGReader: invalid colorType/depth combination' infoPrintCR.
            ^ false.
        ].
        photometric := #palette.
        samplesPerPixel := 1.
        bitsPerSample := Array with:depth.
        ^ true.
    ].

    colorType == 4 ifTrue:[
        depth < 8 ifTrue:[
            'PNGReader: invalid colorType/depth combination' infoPrintCR.
            ^ false.
        ].
        photometric := #blackIs0.
        samplesPerPixel := 2.
        bitsPerSample := Array with:depth with:depth.
        ^ true.
    ].

    colorType == 6 ifTrue:[
        depth < 8 ifTrue:[
            'PNGReader: invalid colorType/depth combination' infoPrintCR.
            ^ false.
        ].
        photometric := #rgb.
        samplesPerPixel := 4.
        bitsPerSample := Array with:depth with:depth with:depth with:depth.
        ^ true.
    ].

    ('PNGReader: invalid colorType: ' , colorType printString , '.') infoPrintCR.
    ^ false
! !

!PNGReader methodsFor:'reading'!

fromStream:aStream
    "read a stream containing a PNG image.
     Leave image description in instance variables."

    |header|

    inStream := aStream.
    aStream binary.

    "PNG-files are always msb (network-world)"
    byteOrder := #msb.

    header := ByteArray new:8.
    aStream nextBytes:8 into:header.

    header ~= (self pngHeader) ifTrue:[
        'PNGReader: not a png file.' infoPrintCR.
        ^ nil
    ].

    (self getIHDRChunk) ifFalse:[
        'PNGReader: required IHDR chunk missing.' infoPrintCR.
        ^ nil
    ].

    compressionMethod ~~ 0 ifTrue:[
        ('PNGReader: compressionMethod ' , compressionMethod printString , ' not supported.') infoPrintCR.
        ^ nil
    ].
    filterMethod > 0 ifTrue:[
        'PNGReader: invalid filterMethod' infoPrintCR.
        ^ nil.
    ].
    interlaceMode > 1 ifTrue:[
        'PNGReader: invalid interlaceMode' infoPrintCR.
        ^ nil.
    ].
    (self setColorType:colorType) ifFalse:[
        ^ nil
    ].

    [self getChunk] whileTrue.

    data := ByteArray new:(self bytesPerRow * height).

    globalDataChunk notNil ifTrue:[
        self processGlobalIDATChunk.
        globalDataChunk := nil.
    ].

    photometric == #palette ifTrue:[
        colorMap isNil ifTrue:[
            'PNGReader: missing palette chunk.' infoPrintCR.
            "/ ^ nil
        ].
    ].

    "
     PNGReader fromFile:'/home/cg/libpng-0.89c/pngtest.png'
    "

    "Modified: / 03-05-2011 / 12:17:34 / cg"
! !

!PNGReader methodsFor:'writing to file'!

pngHeader
    ^ #[137 80 78 71 13 10 26 10]
!

save:image onStream:aStream
    "save image in PNG-file-format onto aStream"

    outStream := aStream.
    outStream binary.

    byteOrder := #msb.
    width := image width.
    height := image height.
    photometric := image photometric.
    samplesPerPixel := image samplesPerPixel.
    bitsPerSample := image bitsPerSample.
    colorMap := image colorMap.
    data := image bits.

    outStream nextPutAll:(self pngHeader).
    self writeIHDRChunk.
    photometric == #palette ifTrue: [self writePaletteChunk].
    self writeImageDataChunk.
    self writeEndChunk
!

writeChunk:chunkTypeChars size:len with:aBlock
    |crc realOutStream chunkBytes|

    realOutStream := outStream.
    outStream := WriteStream on:(ByteArray new:len).

    outStream nextPutBytes:4 from:chunkTypeChars startingAt:1.
    aBlock value.

    chunkBytes := outStream contents.
    crc := CRC32Stream hashValueOf:chunkBytes.

    outStream := realOutStream.

    realOutStream nextPutLong:len MSB:true.
    realOutStream nextPutAll:chunkBytes.
    realOutStream nextPutLong:crc MSB:true.
!

writeEndChunk
    self 
        writeChunk: 'IEND'
        size: 0
        with:[ ]
!

writeFileHeader
    outStream nextPutAll:(self pngHeader)
!

writeIHDRChunk
    |colorType|

    ((photometric == #whiteIs0) or:[ (photometric == #blackIs0)]) ifTrue:[
        colorType := 0.
        samplesPerPixel size > 1 ifTrue:[ colorType := colorType + 4].  "/ +alpha
    ].
    (photometric == #rgb) ifTrue:[
        colorType := 2.
        samplesPerPixel size > 3 ifTrue:[ colorType := colorType + 4].  "/ +alpha
    ].
    (photometric == #palette) ifTrue:[
        colorType := 3.
        samplesPerPixel size > 1 ifTrue:[ colorType := colorType + 4].  "/ +alpha
    ].
    colorType isNil ifTrue:[
        self error:'unjandled photometric'
    ].

    self 
        writeChunk: 'IHDR'
        size: 13
        with:[ 
            self writeLong:width.
            self writeLong:height.
            outStream nextPut: 8.  "Assume that all colors are 24bit"     "/ depth
            outStream nextPut: colorType.  
            outStream nextPut: 0.  "Compression"
            outStream nextPut: 0.  "Filter method"
            outStream nextPut: 0   "Non-interlaced"
        ]
!

writeImageDataChunk
    |compressedByteStream compressedBytes zlibWriter bytesPerScanline idx|

    compressedByteStream := WriteStream on:(ByteArray new:100).
    zlibWriter := ZipStream writeOpenAsZipStreamOn:compressedByteStream suppressHeaderAndChecksum:false.
    zlibWriter binary.

    bytesPerScanline := self bytesPerRow.

    idx := 1.
    0 to:height-1 do:[:y |
        |row|

        row := data copyFrom:idx to:(idx+bytesPerScanline-1).
        zlibWriter nextPutAll:#[0].       "/ no filter
        zlibWriter nextPutAll:row.
        idx := idx + bytesPerScanline.
    ].

    zlibWriter close.
    compressedBytes := compressedByteStream contents.

    self 
        writeChunk: 'IDAT'
        size:(compressedBytes size)
        with:[ 
            outStream nextPutAll:compressedBytes
        ]
!

writePaletteChunk
    self 
        writeChunk: 'PLTE'
        size: 3 * colorMap size
        with:[
            colorMap do:[:color | 
                outStream
                    nextPut: color redByte;
                    nextPut: color greenByte;
                    nextPut: color blueByte
            ]
        ]
! !

!PNGReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/PNGReader.st,v 1.36 2014-12-22 12:00:09 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libview2/PNGReader.st,v 1.36 2014-12-22 12:00:09 cg Exp $'
! !


PNGReader initialize!