PNGReader.st
author Claus Gittinger <cg@exept.de>
Fri, 31 Jul 2009 19:56:56 +0200
changeset 2698 787fb1038266
parent 2697 8e8223bf25af
child 2699 84b52c63e242
permissions -rw-r--r--
more stuff added (but still not complete)

"
 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 redBytes greenBytes blueBytes bytesPerScanline
		globalDataChunk thisScanline prevScanline'
	classVariableNames:''
	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 PNG pictures.
    It is currenty unfinished and untested (need a Zlib inflater).
    In the meantime, use a pngtoXXX converter.

    [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 class methodsFor:'initialization'!

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

    "/ not yet finished - do not add
    "/ MIMETypes defineImageType:'image/x-png'  suffix:'png' reader:self.

    "Modified: 1.2.1997 / 15:02:47 / cg"
! !

!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'!

processBKGDChunkLen:len
    inStream skip:len.
    ^ true

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

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 = '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
!

processIHDRChunkLen:len
    "header chunk - currently unhandled"

    |interlaceMethod palette image bitsPerPixel rowSize|

self halt.        
    width := inStream nextLongMSB:true.   "/ 1..4
    height := inStream nextLongMSB:true.  "/ 5..8
    bitsPerChannel := inStream nextByte.  "/ 9
    colorType := inStream nextByte.       "/ 10
    inStream nextByte. "/ 11
    inStream nextByte. "/ 12
    interlaceMethod := inStream nextByte. "/ 13

    (#(2 4 6) includes: colorType) ifTrue:[
        depth := 32.
        palette := self class defaultPalette.
        image := Image extent: width @ height depth: depth palette: palette
    ].
    (#(0 3) includes: colorType) ifTrue:[ 
        depth := bitsPerChannel min: 8.
        image := Image extent: width @ height
                       depth: depth
                       palette: (colorType = 0 
                                        ifTrue: [self grayColorsFor: depth] 
                                        ifFalse: [palette := self class defaultPalette])].
    "/ bitsPerPixel := (BPP at: colorType + 1) at: bitsPerChannel highBit.
    bytesPerScanline := (width * bitsPerPixel + 7) // 8.
    rowSize := image width * image depth + 31 >> 5
!

processInterlacedDATA:len
    inStream skip:len.
    ^ true
!

processNonInterlacedDATA:len
    | zlibReader filter temp prevScanline thisScanline bytesPerScanline filtersSeen|

    zlibReader := ZipStream readOpenAsZipStreamOn:inStream. 
    "/ 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" copyMethod|

    "/ filtersSeen := Set new.

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

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

    copyMethod := #(copyPixelsGray: nil copyPixelsRGB: copyPixelsIndexed:
                    copyPixelsGrayAlpha: nil copyPixelsRGBA:) at:colorType+1.     

    prevScanline := ByteArray new: bytesPerScanline.
    thisScanline := ByteArray new: bytesPerScanline.
    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].
        zlibReader next: bytesPerScanline into: thisScanline startingAt: 1.
        filter ~~ 0 ifTrue:[ self filterScanline: filter count: bytesPerScanline ].
        self perform:copyMethod with: index.
        temp := prevScanline.
        prevScanline := thisScanline.
        thisScanline := temp
    ]
!

processPHYSChunkLen:len
    "physical pixel chunk - currently unhandled"

    'PNGReader: unhandled chunk type: PHYS' infoPrintCR.
    ^ false
!

processPLTEChunkLen:len
    "read a color palette"

    |n "{ Class: SmallInteger }"|

    (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)
    ].

    ^ 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"
!

processZTXTChunkLen:len
    inStream skip:len.
    ^ true

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

!PNGReader methodsFor:'private-filtering'!

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) 
    ]
!

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)]
!

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

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) 
    ]
!

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-reading'!

copyPixelsRGBA: y
    "Handle non-interlaced RGBA color modes (colorType = 6)"

    |bpr i|

    bpr := self bytesPerRow.
    i := y * bpr.

    data replaceFrom:1+i to:(i+bpr-1) with:thisScanline startingAt:1.
!

getChunk
    |len type crc|

    inStream atEnd ifTrue:[^ false].

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

    Transcript show:'len: '; show:len print; show:' type: '; showCR:type.

    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. ^ false].
    len == 13 ifFalse:[self halt. ^ 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.

    inStream skip:4.
"/    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 := #rgba.
        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
    ].

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

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

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

    "Modified: 21.6.1996 / 21:44: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 := #lsb.
    width := image width.
    height := image height.
    photometric := image photometric.
    samplesPerPixel := image samplesPerPixel.
    bitsPerSample := image bitsPerSample.
    colorMap := image colorMap.
    data := image bits.

    self writeFileHeader.
    self writeHeaderChunk.
    self hasColorPalette ifTrue: [self writePaletteChunk].
    self writeImageChunk.
    self writeEndChunk
!

writeColor:anInteger 
    | color |

    color := colorMap at: (anInteger bitAnd: 16rFFFFFF).
    ^ outStream
        nextPut: (color red / 100 * 255) rounded;
        nextPut: (color green / 100 * 255) rounded;
        nextPut: (color blue / 100 * 255) rounded
!

writeFileHeader
    outStream nextPutAll:(self pngHeader)
!

writeHeaderChunk
    self 
        writeChunk: 'IHDR'
        size: 13
        with:[ 
            self writeLong:width.
            self writeLong:height.
            outStream nextPut: 8.  "Assume that all colors are 24bit"
            outStream nextPut: (colorMap notNil ifTrue: [3] ifFalse: [2]).    "Palette?"
            outStream nextPut: 0.  "Compression"
            outStream nextPut: 0.  "Filter method"
            outStream nextPut: 0   "Non-interlaced"
        ]
!

writePaletteChunk
    self 
        writeChunk: 'PLTE'
        size: 3 * colorMap size
        with:[
            | table |

            table := Array new: colorMap size.
            colorMap keysAndValuesDo: [:key :value | table at: value + 1 put: key].
            table do: [:each | 
                self writeColor: each on: outStream
            ]
        ]
! !

!PNGReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/PNGReader.st,v 1.16 2009-07-31 17:56:56 cg Exp $'
! !

PNGReader initialize!