PNGReader.st
author Claus Gittinger <cg@exept.de>
Sat, 12 May 2018 14:23:45 +0200
changeset 4088 bbf9b58f99c8
parent 4057 d5c48c56f434
child 4099 7695ed8a031f
permissions -rw-r--r--
#FEATURE by cg class: MIMETypes class changed: #initializeFileInfoMappings class: MIMETypes::MIMEType added: #asMimeType #isCHeaderType #isCPPSourceType #isCSourceType

"{ Encoding: utf8 }"

"
 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' }"

"{ NameSpace: Smalltalk }"

ImageReader subclass:#PNGReader
	instanceVariableNames:'colorType bitsPerChannel compressionMethod filterMethod
		interlaceMode bytesPerScanline globalDataChunk thisScanline
		prevScanline processTextChunks specialChunkHandlers
		paletteAlphaEntries paletteIndexForMaskedPixels image forceRGB
		depthImage'
	classVariableNames:'ColorTypeGray ColorTypeGrayAlpha ColorTypePalette ColorTypeRGB
		ColorTypeRGBAlpha 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 provides methods for loading and saving PNG pictures.
    It is currenty unfinished (some interlaced image formats are unsupported, for example: grayscale+alpha)
    In the meantime, use a pngtoXXX converter for interlaced images, and read XXX.

    [caveats:]
        writer can only store mask with depth24 images (for now).
        writer only generates unfiltered non-interlaced data.
        
    [Special:]
        the EnforcedImageTypeQuery is asked for;
        if #rgb is returned AND the image is rgba, then the alpha channel is ignored
        and an rgb (Depth24Image) is returned instead.

    [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.

    ColorTypeGray := 0.
    ColorTypeRGB := 2.
    ColorTypePalette := 3.
    ColorTypeGrayAlpha := 4.
    ColorTypeRGBAlpha := 6.

    "Modified: / 16-02-2017 / 19:41:40 / cg"
! !

!PNGReader class methodsFor:'accessing'!

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

!PNGReader class methodsFor:'queries'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     Any image without mask is supported;
     only depth24 images with mask are (currently)."

    anImage mask notNil ifTrue:[
        "/ for now, can only write depth24 images with mask
        ^ anImage depth == 24
    ].    
    ^ true

    "Modified (comment): / 16-02-2017 / 16:28:53 / 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:'accessing'!

makeImage
    image isNil ifTrue:[
        image := super makeImage.
    ].
    ^ image

    "Created: / 17-02-2017 / 11:14:45 / cg"
!

pngHeader
    <resource: #obsolete>
    ^ self class pngHeader

    "Modified: / 22-02-2017 / 11:00:44 / cg"
! !

!PNGReader methodsFor:'hooks'!

specialChunkHandlerAt:chunkType put:aHandlerBlock
    "define a handler action, which processes unknown chunks.
     The handler block will be called with one or two arguments:
     the binary data of the chunk, and optionally the reader itself"

    specialChunkHandlers isNil ifTrue:[ 
        specialChunkHandlers := Dictionary new
    ].
    specialChunkHandlers at:chunkType put:aHandlerBlock

    "Created: / 14-02-2017 / 11:43:33 / cg"
! !

!PNGReader methodsFor:'reading'!

fromStream:aStream
    "read a stream containing a PNG image.
     Leave the image description in instance variables
     (i.e. to get the image, ask with image)."

    |header bitsPerSampleOut bytesPerScanlineOut|

    inStream := aStream.
    aStream binary.

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

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

    header = (self class pngHeader) ifFalse:[
        Logger warning:'PNGReader: not a png file (%1)' with:aStream.
        Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: not a png file'.
        ^ nil
    ].

    (self getIHDRChunk) ifFalse:[
        Logger warning:'PNGReader: required IHDR chunk missing (%1)' with:aStream.
        Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: required IHDR chunk missing'.
        ^ nil
    ].

    compressionMethod ~~ 0 ifTrue:[
        ('PNGReader: compressionMethod %s not supported.' printfWith:compressionMethod printString) infoPrintCR.
        Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: unsupported compression method'.
        ^ nil
    ].
    filterMethod > 0 ifTrue:[
        'PNGReader: invalid filterMethod' infoPrintCR.
        Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: invalid/unsupported filterMethod'.
        ^ nil.
    ].
    interlaceMode > 1 ifTrue:[
        Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: invalid/unsupported interlaceMode'.
        'PNGReader: invalid interlaceMode' infoPrintCR.
        ^ nil.
    ].
    (self setColorType:colorType) ifFalse:[
        ^ nil
    ].

    [self getChunk] whileTrue.

    "/ kludge: if we get a grey image with alpha,
    "/ load as rgb+alpha
    forceRGB := false. 
    depthImage := depth.
    
    "/ bytesPerScanline is always the in-bytesPerScanline
    bytesPerScanline := self bytesPerRow.
    bytesPerScanlineOut := bytesPerScanline.
    
    samplesPerPixel == 2 ifTrue:[
        photometric == #blackIs0 ifTrue:[
            depth == 16 ifTrue:[
                "/ force to r8+g8+b8+a8
                forceRGB := true. 
                depthImage := 32.
                bytesPerScanlineOut := width * 4.
                bitsPerSampleOut := #[8 8 8 8].
            ] ifFalse:[
                depth == 32 ifTrue:[
                    "/ force to r8+g8+b8+a8
                    forceRGB := true. 
                    depthImage := 32.
                    bytesPerScanlineOut := width * 4.
                    bitsPerSampleOut := #[8 8 8 8].
                ] ifFalse:[
                    self halt.
                ].    
            ].    
        ].    
    ].
    
    data := ByteArray new:(bytesPerScanlineOut * height).
    
    globalDataChunk notNil ifTrue:[
        self processGlobalIDATChunk.
        globalDataChunk := nil.
    ].

    photometric == #palette ifTrue:[
        colorMap isNil ifTrue:[
            Image badImageFormatQuerySignal raiseRequestErrorString:'PNGReader: palette chunk missing'.
            'PNGReader: palette chunk missing.' infoPrintCR.
            "/ ^ nil
        ].
    ].
    
    paletteAlphaEntries notNil ifTrue:[
        "/ this vector now provides alpha values.
        "/ for now, we can only deal with 0/255 alpha values...
        self generateMaskFromPaletteAlphaEntries
    ].
    
    forceRGB ifTrue:[ 
        depth := depthImage.
        photometric := #rgba.
        bitsPerSample := bitsPerSampleOut.
        samplesPerPixel := 4.
    ].    

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

     Verbose := true.
     PNGReader fromFile:(RegressionTests::ImageReaderTest packageDirectory construct:'testData/pngImages/tbbn3p08.png')
     
    "

    "Modified: / 17-09-2017 / 15:30:45 / cg"
! !

!PNGReader methodsFor:'reading-private'!

generateMaskFromPaletteAlphaEntries
    image isNil ifTrue:[
        self makeImage
    ].
    
    colorType == ColorTypePalette ifTrue:[        
        image depth == 8 ifTrue:[
            "/ if there is only one entry to care for...
            (paletteAlphaEntries occurrencesOf:0) == 1 ifTrue:[
                (paletteAlphaEntries conform:[:alpha | (alpha == 0) or:[alpha == 255]]) ifTrue:[
                    image mask:(self class 
                                    buildMaskFromColor:(paletteAlphaEntries indexOf:0)-1 
                                    for:data depth:(image depth)
                                    width:width height:height).
                    ^ self
                ].    
            ].    
        ].
        
        "/ multiple masked pixels...
        paletteAlphaEntries keysAndValuesDo:[:pixelIndex :alpha |
            alpha == 255 ifTrue:[
                image createMaskForPixelValue:pixelIndex
            ] ifFalse:[
                alpha == 0 ifTrue:[
                    "/ ok; already
                ] ifFalse:[
                    image createMaskForPixelValue:pixelIndex
                ]    
            ].
        ].
        "/ image mask:nil.
        ^ self.
    ].
    
    colorType == ColorTypeGray ifTrue:[
        |maskPixel|

        maskPixel := paletteAlphaEntries unsignedInt16At:1 MSB:true.
        image createMaskForPixelValue:maskPixel.
        ^ self 
    ].    
    colorType == ColorTypeRGB ifTrue:[
        |mr mg mb maskPixel|
        
        mr := paletteAlphaEntries unsignedInt16At:1 MSB:true.
        mg := paletteAlphaEntries unsignedInt16At:3 MSB:true.
        mb := paletteAlphaEntries unsignedInt16At:5 MSB:true.
        depth <= 32 ifTrue:[
            "/ only use the low bits...
            mr > 255 ifTrue:[ self error:'only 8bit RGB supported'].
            mg > 255 ifTrue:[ self error:'only 8bit RGB supported'].
            mb > 255 ifTrue:[ self error:'only 8bit RGB supported'].
            maskPixel := ((mr bitShift:16) bitOr:(mg bitShift:8)) bitOr:mb.
        ] ifFalse:[
            maskPixel := ((mr bitShift:32) bitOr:(mg bitShift:16)) bitOr:mb.
        ].   
        image createMaskForPixelValue:maskPixel.
        ^ self 
    ].

    "Created: / 17-02-2017 / 08:07:04 / cg"
    "Modified: / 23-08-2017 / 17:24:30 / cg"
!

getChunk
    |len type crc|

    inStream atEnd ifTrue:[^ false].

    len := inStream nextInt32MSB: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 nextInt32MSB: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 nextInt32MSB:true.

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

    type = 'IHDR' ifFalse:[
        Logger warning:'PNGReader: expected IHDR magic (%1)' with:inStream.
        ^ false
    ].
    len == 13 ifFalse:[
        Logger warning:'PNGReader: bad IHDR size (%1)' with:inStream.
        ^ false
    ].

    width := inStream nextInt32MSB:true.        
    height := inStream nextInt32MSB:true.        

    (width <= 0 or:[height <= 0]) ifTrue:[
        Logger warning:'PNGReader: invalid dimension(s) (%1)' with:inStream.
        ^ false.
    ].
    self reportDimension.

    bitsPerChannel := inStream nextByte.
    depth := bitsPerChannel. "/ for now - might be changed by setColorType.
    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:   bitsPerChannel: ' infoPrint. bitsPerChannel infoPrintCR.
        'PNGReader:   colorType: ' infoPrint. colorType infoPrintCR.
        'PNGReader:   compressionMethod: ' infoPrint. compressionMethod infoPrintCR.
        'PNGReader:   filterMethod: ' infoPrint. filterMethod infoPrintCR.
        'PNGReader:   interlaceMode: ' infoPrint. interlaceMode infoPrintCR.
    ].

    crc := inStream nextInt32MSB:true.
    ^ true

    "Modified: / 17-02-2017 / 11:35:20 / cg"
    "Modified (comment): / 31-08-2017 / 18:03:41 / cg"
!

handleText:text keyword:keyword
    "/ things like exif data etc.
    "/ self halt.

    "/Standard keywords for text chunks:
    "/
    "/   Title            Short (one line) title or caption for image
    "/   Author           Name of image's creator
    "/   Description      Description of image (possibly long)
    "/   Copyright        Copyright notice
    "/   Creation Time    Time of original image creation
    "/   Software         Software used to create the image
    "/   Disclaimer       Legal disclaimer
    "/   Warning          Warning of nature of content
    "/   Source           Device used to create the image
    "/   Comment          Miscellaneous comment; conversion from
    "/                    GIF comment
!

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

    colorType == ColorTypeRGB "2" ifTrue:[
        photometric := #rgb.
        samplesPerPixel := 3.
        bitsPerSample := Array with:bitsPerChannel with:bitsPerChannel with:bitsPerChannel.
        depth := bitsPerChannel * 3.

        bitsPerChannel < 8 ifTrue:[
            bitsPerChannel == 5 ifTrue:[
                depth := 16
            ] ifFalse:[
                ('PNGReader: unsupported bitsPerChannel:%1 for colorType rgb' bindWith:bitsPerChannel) infoPrintCR.
            ].    
        ].
        ^ true.
    ].

    colorType == ColorTypePalette "3" ifTrue:[
        bitsPerChannel == 16 ifTrue:[
            'PNGReader: invalid unsupported bitsPerChannel:%1 for colorType palette' infoPrintCR.
            ^ false.
        ].
        photometric := #palette.
        samplesPerPixel := 1.
        bitsPerSample := Array with:bitsPerChannel.
        depth := bitsPerChannel.
        ^ true.
    ].

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

    colorType == ColorTypeRGBAlpha "6" ifTrue:[
        bitsPerChannel < 8 ifTrue:[
            'PNGReader: unsupported colorType/depth combination' infoPrintCR.
            ^ false.
        ].
        photometric := #rgba.
        ImageReader::EnforcedImageTypeQuery query == #rgb ifTrue:[
            photometric := #rgb
        ].
        samplesPerPixel := 4.
        bitsPerSample := Array with:bitsPerChannel with:bitsPerChannel with:bitsPerChannel with:bitsPerChannel.
        depth := bitsPerChannel * 4.
        ^ true.
    ].

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

    "Modified: / 31-08-2017 / 17:58:18 / cg"
! !

!PNGReader methodsFor:'reading-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 nextInt32MSB:true) / 100000.0.
    whitePointY := (inStream nextInt32MSB:true) / 100000.0.
    redX := (inStream nextInt32MSB:true) / 100000.0.
    redY := (inStream nextInt32MSB:true) / 100000.0.
    greenX := (inStream nextInt32MSB:true) / 100000.0.
    greenY := (inStream nextInt32MSB:true) / 100000.0.
    blueX := (inStream nextInt32MSB:true) / 100000.0.
    blueY := (inStream nextInt32MSB: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 isNil ifTrue:[
            globalDataChunk := ReadWriteStream on:(ByteArray new:(height * self bytesPerRow)).
        ].
        globalDataChunk nextPutAll:chunk.
        ^ true
    ].

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

    type = 'iTXt' ifTrue:[^ self processITXTChunkLen:len].
    type = 'iCCP' ifTrue:[^ self processICCPChunkLen:len].
    type = 'hIST' ifTrue:[^ self processHISTChunkLen:len].
    type = 'spAL' ifTrue:[^ self processSPALChunkLen:len].

    specialChunkHandlers notNil ifTrue:[
        |handler chunkData|
        
        handler := specialChunkHandlers at:type ifAbsent:nil.
        handler notNil ifTrue:[
            chunkData := inStream nextBytes:len.
            handler value:chunkData optionalArgument:self.
            ^ true.
        ].
    ].

    type = 'niVI' ifTrue:[^ self processNIVIChunkLen:len].
    type = 'exEX' ifTrue:[^ self processEXEXChunkLen:len].

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

    inStream skip:len.
    ^ true.

    "Created: / 21-06-1996 / 21:10:37 / cg"
    "Modified: / 11-04-2017 / 17:04:12 / cg"
!

processEXEXChunkLen:len    
    "/ this cunk contains an expecco sample network.
    "/ ...to read it (using the expecco importer),
    "/ create a reader with a chunkHook and extract it there.
    Logger info:('PNG: skip exEX chunk').
    inStream skip:len.
    ^ true.

    "Created: / 11-04-2017 / 17:06:27 / cg"
!

processGAMAChunkLen:len
    inStream skip:len.
    ^ true

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

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

processHISTChunkLen:len
    "/ ignored
    "/ inStream nextBytes:len.

    inStream skip:len.
    ^ true

    "Created: / 17-02-2017 / 11:31:36 / cg"
!

processICCPChunkLen:len
    "/ ignored
    "/ inStream nextBytes:len.

    inStream skip:len.
    ^ true

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

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

processIHDRChunkLen:len
    "/ ignored
    
    inStream skip:len.
    ^ true

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

processITXTChunkLen:len
    "/ international (i.e.utf8) textual data.
    
    "/ currently ignored - not needed to display png images
    "/
    "/   Keyword:             1-79 bytes (character string)
    "/   Null separator:      1 byte
    "/   Compression flag:    1 byte
    "/   Compression method:  1 byte
    "/   Language tag:        0 or more bytes (character string)
    "/   Null separator:      1 byte
    "/   Translated keyword:  0 or more bytes
    "/   Null separator:      1 byte
    "/   Text:                0 or more bytes

    "/ if needed, set processTextChunks to true somewhere...
    processTextChunks == true ifTrue:[
        |chunkData keyword text i1 i2 i3 
         compressionFlag compressionMethod languageTag
         xlatedKeyword textBytes|

        chunkData := inStream nextBytes:len.
        i1 := chunkData indexOf:0.
        keyword := (chunkData copyTo:i1-1) asString.
        compressionFlag := chunkData at:i1+1.
        compressionMethod := chunkData at:i1+2.
        i2 := chunkData indexOf:0 startingAt:i1+3.
        languageTag := (chunkData copyFrom:i1+3 to:i2-1) asString.
        i3 := chunkData indexOf:0 startingAt:i2+1.
        xlatedKeyword := (chunkData copyFrom:i2+1 to:i3-1) asString.
        textBytes := chunkData copyFrom:i3+1.
        compressionFlag == 0 ifTrue:[
            text := textBytes
        ] ifFalse:[
            compressionFlag == 1 ifTrue:[
                "/ for now, only zlib compression is supported...
                "/ ... no - not even that is
                Logger warning:'PNG: zlib compressed text currently unsupported'.
            ] ifFalse:[
                Logger warning:'PNG: unsupported text compression method'.
            ].    
        ].    
        text := text utf8Decoded.
        self handleText:text keyword:keyword.
    ] ifFalse:[    
        inStream skip:len.
    ].
    ^ true

    "Created: / 21-06-1996 / 21:15:58 / cg"
    "Modified: / 16-02-2017 / 19:51:21 / cg"
!

processInterlacedDATA:len
    inStream skip:len.
    ^ true
!

processInterlacedGlobalDATA
    "adam7 interlace method"

    | zlibReader filter 
      bytesPerPass startingCol colIncrement rowIncrement 
      startingRow 
      temp "filtersSeen"  
      cx       "{ Class: SmallInteger }"
      sc       "{ Class: SmallInteger }"
      cy       "{ Class: SmallInteger }"
      startRow "{ Class: SmallInteger }"
      w        "{ Class: SmallInteger }"
      h        "{ Class: SmallInteger }"
    |

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

    globalDataChunk reset.
    zlibReader := ZipStream readOpenAsZipStreamOn:globalDataChunk suppressHeaderAndChecksum:false.
    zlibReader binary.

    h := height.
    w := width.
    1 to: 7 do: [:pass |
        (self doPass: pass) ifTrue:[
            cx := colIncrement at: pass.
            sc := startingCol at: pass.
            cy := rowIncrement at: pass.
            bytesPerPass := (((w - sc + cx - 1) // cx * depth) + 7) // 8.
            prevScanline := ByteArray new: bytesPerPass.
            thisScanline := ByteArray new: bytesPerScanline.
            startRow := startingRow at: pass.
            startRow to: h-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"
!

processNIVIChunkLen:len    
    "/ this cunk contains a labView vi.
    "/ ignored for now...
    "/ ...to read it (using the expecco importer),
    "/ create a reader with a chunkHook and extract it there.
    Logger info:('PNG: skip niVI chunk').
    inStream skip:len.
    ^ true.

    "Created: / 14-02-2017 / 08:57:29 / cg"
    "Modified: / 14-02-2017 / 22:36:34 / 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 "filtersSeen" i|

    "/ filtersSeen := Set new.

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

    globalDataChunk reset.
    zlibReader := ZipStream readOpenAsZipStreamOn:globalDataChunk suppressHeaderAndChecksum:false.
    zlibReader binary.

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

    "Modified: / 16-02-2017 / 16:45:52 / cg"
    "Modified (format): / 23-08-2017 / 17:05:01 / cg"
!

processPHYSChunkLen:len
    "physical pixel chunk - currently unhandled"

    |pixelPerUnitX pixelPerUnitY unit|

    pixelPerUnitX := inStream nextInt32MSB:true.  
    pixelPerUnitY := inStream nextInt32MSB: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
     triple|

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

    triple := ByteArray new:3.
    
    1 to:n do:[:i |
        inStream next:3 into:triple startingAt:1.
        redBytes at:i put:(triple at:1).
        greenBytes at:i put:(triple at:2).
        blueBytes at:i put:(triple at:3)
    ].

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

    ^ true

    "Created: / 21-06-1996 / 21:22:28 / cg"
    "Modified: / 23-08-2017 / 16:58:04 / cg"
!

processSBITChunkLen:len
    inStream skip:len.
    ^ true

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

processSPALChunkLen:len
    "/ ignored
    "/ inStream nextBytes:len.

    inStream skip:len.
    ^ true

    "Created: / 17-02-2017 / 11:31:40 / cg"
!

processTEXTChunkLen:len    
    "/ textual data in iso8859 coding.

    "/ currently ignored - not needed to display png images
    "/   Keyword:        1-79 bytes (character string)
    "/   Null separator: 1 byte
    "/   Text:           n bytes (character string)

    "/ if needed, set processTextChunks to true somewhere...
    processTextChunks == true ifTrue:[
        |chunkData keyword text i|

        chunkData := inStream nextBytes:len.
        i := chunkData indexOf:0.
        keyword := (chunkData copyTo:i-1) asString.
        text := (chunkData copyFrom:i+1) asString.
        self handleText:text keyword:keyword.
    ] ifFalse:[  
        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
    paletteAlphaEntries := inStream nextBytes:len.
    
    colorType == ColorTypeRGB ifTrue:[
        len ~~ 3 ifTrue:[
            Logger warning:'PNG: bad trns chunk size'.
            paletteAlphaEntries := nil.
        ].
        ^ true
    ].    
    colorType == ColorTypePalette ifTrue:[
        len ~~ 1 ifTrue:[
            Logger warning:'PNG: bad trns chunk size'.
            paletteAlphaEntries := nil.
        ].
        ^ true
    ].        
    colorType == ColorTypeGray ifTrue:[
        len ~~ 2 ifTrue:[
            Logger warning:'PNG: bad trns chunk size'.
            paletteAlphaEntries := nil.
        ].
        ^ true
    ].        
    paletteAlphaEntries := nil.
    ^ true

    "Modified (format): / 17-02-2017 / 16:57:27 / cg"
!

processZTXTChunkLen:len
    "/ compressed text
    
    "/ currently ignored - not needed to display png images
    inStream skip:len.
    ^ true

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

!PNGReader methodsFor:'reading-private filtering'!

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

%{
    if (__isByteArray(__INST(thisScanline))
     && __isByteArray(__INST(prevScanline))
     && __isSmallInteger(__INST(depth))
     && __isSmallInteger(count)) {
        unsigned char *__thisScanline = __byteArrayVal(__INST(thisScanline));
        unsigned int __sz_this = __byteArraySize(__INST(thisScanline));
        unsigned char *__prevScanline = __byteArrayVal(__INST(prevScanline));
        unsigned int __sz_prev = __byteArraySize(__INST(prevScanline));
        INT __count = __intVal(count);
        INT __delta = __intVal(__INST(depth)) / 8;
        int __i;

        if (__delta < 1) __delta = 1;
        for (__i=0; __i<__delta; __i++) {
            __thisScanline[__i] += (__prevScanline[__i] >> 1);
        }
        for (; __i < __count; __i++) {
            __thisScanline[__i] += ((__prevScanline[__i] + __thisScanline[__i-__delta]) >> 1);
        }
        RETURN(self);
    }
%}.

    delta := depth // 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|

%{
    if (__isByteArray(__INST(thisScanline))
     && __isByteArray(__INST(prevScanline))
     && __isSmallInteger(__INST(depth))
     && __isSmallInteger(count)) {
        unsigned char *__thisScanline = __byteArrayVal(__INST(thisScanline));
        unsigned int __sz_this = __byteArraySize(__INST(thisScanline));
        unsigned char *__prevScanline = __byteArrayVal(__INST(prevScanline));
        unsigned int __sz_prev = __byteArraySize(__INST(prevScanline));
        INT __count = __intVal(count);
        INT __delta = __intVal(__INST(depth)) / 8;
        int __i;

        if (__delta < 1) __delta = 1;
        for (__i = __delta; __i < __count; __i++) {
            __thisScanline[__i] = __thisScanline[__i] + __thisScanline[__i-__delta];
        }
        RETURN(self);
    }
%}.

    delta := depth // 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|

%{
    if (__isByteArray(__INST(thisScanline))
     && __isByteArray(__INST(prevScanline))
     && __isSmallInteger(__INST(depth))
     && __isSmallInteger(count)) {
        unsigned char *__thisScanline = __byteArrayVal(__INST(thisScanline));
        unsigned int __sz_this = __byteArraySize(__INST(thisScanline));
        unsigned char *__prevScanline = __byteArrayVal(__INST(prevScanline));
        unsigned int __sz_prev = __byteArraySize(__INST(prevScanline));
        INT __count = __intVal(count);
        INT __delta = __intVal(__INST(depth)) / 8;
        int __i;
        
        if (__delta < 1) __delta = 1;
        for (__i=0; __i<__delta; __i++) {
            unsigned int __pix = __thisScanline[__i] + __prevScanline[__i];
            __thisScanline[__i] = __pix;
        }
        for (; __i < __count; __i++) {
            int __pCenter = __thisScanline[__i];
            int __pLeft = __thisScanline[__i - __delta];
            int __pAbove = __prevScanline[__i];
            int __pAboveLeft = __prevScanline[__i - __delta];
            int __pa, __pb, __pc;
            int __p;
            
            __pa = (__pAbove - __pAboveLeft); 
            __pa = __pa < 0 ? -__pa : __pa;
            __pb = (__pLeft - __pAboveLeft);
            __pb = __pb < 0 ? -__pb : __pb;
            __pc = __pLeft + __pAbove - __pAboveLeft - __pAboveLeft;
            __pc = __pc < 0 ? -__pc : __pc; 
            if ((__pa <= __pb) && (__pa <= __pc)) __p = __pLeft;
            else if (__pb <= __pc) __p = __pAbove;
            else __p = __pAboveLeft;
            
            __thisScanline[__i] = __pCenter + __p;
        }
        RETURN(self);
    }
%}.

    delta := depth // 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
    filterType == 0 ifTrue:[^ self].
    
    self 
        perform:(#(filterHorizontal: filterVertical: filterAverage: filterPaeth:) at:filterType)
        with:count

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

filterVertical:count 
    "Use the pixel above as a predictor"
    
%{
    if (__isByteArray(__INST(thisScanline))
     && __isByteArray(__INST(prevScanline))
     && __isSmallInteger(count)) {
        unsigned char *__thisScanline = __byteArrayVal(__INST(thisScanline));
        unsigned int __sz_this = __byteArraySize(__INST(thisScanline));
        unsigned char *__prevScanline = __byteArrayVal(__INST(prevScanline));
        unsigned int __sz_prev = __byteArraySize(__INST(prevScanline));
        INT __count = __intVal(count);
        int __i;

        for (__i=0; __i<__count; __i++) {
            unsigned int __pix = __thisScanline[__i] + __prevScanline[__i];
            __thisScanline[__i] = __pix;
        }
        RETURN(self);
    }
%}.

    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: l above: a aboveLeft: al
    "Predicts the value of a pixel based on nearby pixels, based on Paeth (GG II, 1991)"

    | pa pb pc |

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

!PNGReader methodsFor:'reading-private pixel copy'!

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

    "/ per color type copy methods
    s := #( 
             #copyPixelsGray:at:by:         "/ 0 = ColorTypeGray
             nil
             #copyPixelsRGB:at:by:          "/ 2 = ColorTypeRGB
             #copyPixelsIndexed:at:by:      "/ 3 = ColorTypePalette
             #copyPixelsGrayAlpha:at:by:    "/ 4 = ColorTypeGrayAlpha
             nil 
             #copyPixelsRGBA:at:by:         "/ 6 = ColorTypeRGBA
        ) at:colorType + 1.
    self perform:s with:y with:startX with:incX

    "Modified: / 03-05-2011 / 12:02:45 / cg"
    "Modified (comment): / 16-02-2017 / 19:42:47 / cg"
!

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

    |srcIndex "{ Class: SmallInteger }"
     srcMask  "{ Class: SmallInteger }"
     nPixels  "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     dstMask  "{ Class: SmallInteger }"
     x        "{ Class: SmallInteger }"
     bits     "{ Class: SmallInteger }"
     bitMask  "{ Class: SmallInteger }"
     rS       "{ Class: SmallInteger }"
     lS       "{ Class: SmallInteger }"
     rowIndex "{ Class: SmallInteger }"|
    
    nPixels := width // incX.
    srcIndex := 0. srcMask := 0. x := startX.

    depth == 1 ifTrue:[
        dstIndex := (y * bytesPerScanline) + (startX // 8) + 1.
        dstMask := 16r80 >> (x \\ 8).

        1 to:nPixels do:[:cnt |
            srcMask == 0 ifTrue:[
                srcMask := 16r80.
                srcIndex := srcIndex + 1.
                bits := thisScanline at:srcIndex. 
            ].
            bitMask := (bits bitAnd:srcMask) == 0 ifTrue:[0] ifFalse:[dstMask].
            bitMask ~~ 0 ifTrue:[
                data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
            ].    
            x := x + incX.
            dstMask := dstMask >> incX.
            dstMask == 0 ifTrue:[
                dstIndex := dstIndex + 1.
                dstMask := 16r80 >> (x \\ 8).
            ].
            srcMask := srcMask bitShift:-1.
        ].
        ^ self.
    ].
    
    depth == 2 ifTrue:[
        dstIndex := (y * bytesPerScanline) + (startX // 4) + 1.
        lS := 6 - ((x \\ 4) * 2).
        rS := -1. 
        1 to:nPixels do:[:cnt |
            rS < 0 ifTrue:[
                srcIndex := srcIndex + 1.
                bits := thisScanline at:srcIndex.
                rS := 6.
            ].
            bitMask := ((bits >> rS) bitAnd:2r11).
            bitMask ~~ 0 ifTrue:[
                bitMask := bitMask << lS.
                data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
            ].    
            lS := lS - (incX * 2).
            lS < 0 ifTrue:[
                lS <= -8 ifTrue:[
                    dstIndex := dstIndex + 2.
                    lS := lS + 8 + 8.
                ] ifFalse:[
                    dstIndex := dstIndex + 1.
                    lS := lS + 8.
                ].    
            ].
            rS := rS - 2.
        ].
        ^ self.
    ].
    
    depth == 4 ifTrue:[
        rowIndex := (y * bytesPerScanline) + 1.
        dstIndex := rowIndex + (x // 2).
        rS := -1. 
        1 to:nPixels do:[:cnt |
            rS < 0 ifTrue:[
                srcIndex := srcIndex + 1.
                bits := thisScanline at:srcIndex.
                rS := 4.
            ].
            bitMask := ((bits >> rS) bitAnd:2r1111).
            x even ifTrue:[    
                bitMask := bitMask bitShift:4.
            ].    
            data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
            x := x + incX.
            dstIndex := rowIndex + (x // 2).
            rS := rS - 4.
        ].
        ^ self.
    ].
    
    depth == 8 ifTrue:[
        srcIndex := 1.
        dstIndex := (y * bytesPerScanline) + (startX) + 1.

        1 to:nPixels do:[:n |
            data at:dstIndex put:(thisScanline at:srcIndex).
            srcIndex := srcIndex + 1.
            dstIndex := dstIndex + incX
        ].
        ^ self.
    ].

    depth == 16 ifTrue:[
        srcIndex := 1.
        dstIndex := (y * bytesPerScanline) + (startX*2) + 1.

        1 to:nPixels do:[:n |
            data unsignedInt16At:dstIndex put:(thisScanline unsignedInt16At:srcIndex).
            srcIndex := srcIndex + 2.
            dstIndex := dstIndex + (incX * 2)
        ].
        ^ self.
    ].
    self error:'unsupported depth'.
!

copyPixelsGrayAlpha:y at:startX by:incX 
    "Handle interlaced pixels of supported colorTypes."

    |srcIndex "{ Class: SmallInteger }"
     srcMask  "{ Class: SmallInteger }"
     nPixels  "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     dstMask  "{ Class: SmallInteger }"
     x        "{ Class: SmallInteger }"
     bits     "{ Class: SmallInteger }"
     bitMask  "{ Class: SmallInteger }"
     rS       "{ Class: SmallInteger }"
     lS       "{ Class: SmallInteger }"
     rowIndex "{ Class: SmallInteger }"
     pix alpha gray|
    
    nPixels := width // incX.
    srcIndex := 0. srcMask := 0. x := startX.

"/    depth == 1 ifTrue:[
"/        dstIndex := (y * bytesPerScanline) + (startX // 8) + 1.
"/        dstMask := 16r80 >> (x \\ 8).
"/
"/        1 to:nPixels do:[:cnt |
"/            srcMask == 0 ifTrue:[
"/                srcMask := 16r80.
"/                srcIndex := srcIndex + 1.
"/                bits := thisScanline at:srcIndex. 
"/            ].
"/            bitMask := (bits bitAnd:srcMask) == 0 ifTrue:[0] ifFalse:[dstMask].
"/            bitMask ~~ 0 ifTrue:[
"/                data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
"/            ].    
"/            x := x + incX.
"/            dstMask := dstMask >> incX.
"/            dstMask == 0 ifTrue:[
"/                dstIndex := dstIndex + 1.
"/                dstMask := 16r80 >> (x \\ 8).
"/            ].
"/            srcMask := srcMask bitShift:-1.
"/        ].
"/        ^ self.
"/    ].
"/    
"/    depth == 2 ifTrue:[
"/        dstIndex := (y * bytesPerScanline) + (startX // 4) + 1.
"/        lS := 6 - ((x \\ 4) * 2).
"/        rS := -1. 
"/        1 to:nPixels do:[:cnt |
"/            rS < 0 ifTrue:[
"/                srcIndex := srcIndex + 1.
"/                bits := thisScanline at:srcIndex.
"/                rS := 6.
"/            ].
"/            bitMask := ((bits >> rS) bitAnd:2r11).
"/            bitMask ~~ 0 ifTrue:[
"/                bitMask := bitMask << lS.
"/                data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
"/            ].    
"/            lS := lS - (incX * 2).
"/            lS < 0 ifTrue:[
"/                lS <= -8 ifTrue:[
"/                    dstIndex := dstIndex + 2.
"/                    lS := lS + 8 + 8.
"/                ] ifFalse:[
"/                    dstIndex := dstIndex + 1.
"/                    lS := lS + 8.
"/                ].    
"/            ].
"/            rS := rS - 2.
"/        ].
"/        ^ self.
"/    ].
"/    
"/    depth == 4 ifTrue:[
"/        rowIndex := (y * bytesPerScanline) + 1.
"/        dstIndex := rowIndex + (x // 2).
"/        rS := -1. 
"/        1 to:nPixels do:[:cnt |
"/            rS < 0 ifTrue:[
"/                srcIndex := srcIndex + 1.
"/                bits := thisScanline at:srcIndex.
"/                rS := 4.
"/            ].
"/            bitMask := ((bits >> rS) bitAnd:2r1111).
"/            x even ifTrue:[    
"/                bitMask := bitMask bitShift:4.
"/            ].    
"/            data at:dstIndex put:((data at:dstIndex) bitOr:bitMask).
"/            x := x + incX.
"/            dstIndex := rowIndex + (x // 2).
"/            rS := rS - 4.
"/        ].
"/        ^ self.
"/    ].
"/    
"/    depth == 8 ifTrue:[
"/        srcIndex := 1.
"/        dstIndex := (y * bytesPerScanline) + (startX) + 1.
"/
"/        1 to:nPixels do:[:n |
"/            data at:dstIndex put:(thisScanline at:srcIndex).
"/            srcIndex := srcIndex + 1.
"/            dstIndex := dstIndex + incX
"/        ].
"/        ^ self.
"/    ].

    forceRGB ifTrue:[
        (depth == 16 and:[depthImage == 32]) ifTrue:[
            "/ converting gray8+alpha8 to r8+g8+b8+alpha8

            srcIndex := 1.
            dstIndex := (y * (width * 4)) + (startX*4) + 1.

            1 to:nPixels do:[:n |
                pix := thisScanline unsignedInt16At:srcIndex.
                alpha := pix bitAnd:16rFF.
                gray := (pix rightShift:8) bitAnd:16rFF.
                "/ put r-g-b-a
                data at:dstIndex put:gray.
                data at:dstIndex+1 put:gray.
                data at:dstIndex+2 put:gray.
                data at:dstIndex+3 put:alpha.

                srcIndex := srcIndex + 2.
                dstIndex := dstIndex + (incX * 4)
            ].
            ^ self.
        ].
        (depth == 32 and:[depthImage == 32]) ifTrue:[
            "/ converting gray16+alpha16 to r8+g8+b8+alpha8

            srcIndex := 1.
            dstIndex := (y * (width * 4)) + (startX*4) + 1.

            1 to:nPixels do:[:n |
                pix := thisScanline unsignedInt32At:srcIndex.
                
                alpha := pix bitAnd:16rFFFF.
                gray := (pix rightShift:16) bitAnd:16rFFFF.
                "/ reduce to 8 bit
                alpha := alpha rightShift:8.
                gray := gray rightShift:8.
                
                "/ put r-g-b-a
                data at:dstIndex put:gray.
                data at:dstIndex+1 put:gray.
                data at:dstIndex+2 put:gray.
                data at:dstIndex+3 put:alpha.

                srcIndex := srcIndex + 4.
                dstIndex := dstIndex + (incX * 4)
            ].
            ^ self.
        ].
    ].
    self error:'unsupported depth'.

    "Created: / 17-09-2017 / 14:20:24 / cg"
    "Modified: / 17-09-2017 / 15:28:38 / cg"
!

copyPixelsIndexed:y at:startX by:incX 
    self copyPixelsGray:y at:startX by:incX 
!

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

    |srcIndex "{ Class: SmallInteger }" 
     nPixels  "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     dstInc   "{ Class: SmallInteger }"
     bpp      "{ Class: SmallInteger }"|

    bpp := bytesPerScanline // width.
    
    "/ 1 byte per r,g,b
    srcIndex := 1.
    dstIndex := (y * bytesPerScanline) + (startX * bpp) + 1.
    dstInc := incX * bpp.

    nPixels := width // incX.
    1 to:nPixels do:[:n |
        data replaceFrom:dstIndex to:dstIndex+bpp-1 with:thisScanline startingAt:srcIndex.
        srcIndex := srcIndex + bpp.
        dstIndex := dstIndex + dstInc
    ].
!

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

    |srcIndex "{ Class: SmallInteger }"
     nPixels  "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     dstInc   "{ Class: SmallInteger }"|

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

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.
    mask := image mask.
    depth := self bitsPerPixel.

    outStream nextPutAll:(self class pngHeader).
    
    image mask notNil ifTrue:[
        ((photometric ~~ #rgb) and:[(photometric ~~ #rgba) and:[(photometric ~~ #argb)]]) ifTrue: [
            self determinePaletteIndexForMaskedPixels
        ] ifFalse:[
            photometric := #rgba.
        ].    
    ].

    self writeIHDRChunk.
    photometric == #palette ifTrue: [self writePaletteChunk].
    paletteIndexForMaskedPixels notNil ifTrue: [self writeTRNSChunk].
    self writeImageDataChunk.
    self writeEndChunk

    "Modified: / 23-08-2017 / 16:25:00 / cg"
    "Modified (format): / 31-08-2017 / 17:26:28 / cg"
! !

!PNGReader methodsFor:'writing-private'!

determinePaletteIndexForMaskedPixels
    "/ if all masked pixels are 0, and 0 is not used elsewhere in the image,
    "/ write it as such.
    "/ Otherwise, find an unallocated palette index, and assign masked pixels to it.

    |usedPixels freePixels pixelIdx|

    colorMap size < 256 ifTrue:[
        paletteIndexForMaskedPixels := colorMap size.
    ] ifFalse:[    
        usedPixels := data usedValues.
        usedPixels size == 256 ifTrue:[
            self error:'cannot represent image (no palette slot for mask)'
        ].
        freePixels := (0 to:255) asSet removeAllFoundIn:usedPixels.
        paletteIndexForMaskedPixels := freePixels first.
    ].    

    "/ rewrite data: wherever masked, change pixel to paletteIndexForMaskedPixels
    
    data := data copy.
    pixelIdx := 1.
    0 to:height-1 do:[:y |
        0 to:width-1 do:[:x |
            (mask pixelAtX:x y:y) == 0 ifTrue:[
                data at:pixelIdx put:paletteIndexForMaskedPixels.
            ].
            pixelIdx := pixelIdx + 1
        ]
    ].
    
    "       
     PNGReader save:(ToolbarIconLibrary systemBrowserIcon) onFile:'/tmp/icon.png'
     ImageEditor openOnFile:'/tmp/icon.png'
    "

    "Created: / 16-02-2017 / 19:59:39 / cg"
    "Modified: / 17-02-2017 / 09:25:57 / cg"
! !

!PNGReader methodsFor:'writing-private chunks'!

determineColorTypeAndHasMask
    "sets colorType as side effect;
     returns boolean if a mask is present"
     
    ((photometric == #whiteIs0) or:[ (photometric == #blackIs0)]) ifTrue:[
        colorType := ColorTypeGray.
        ^ (samplesPerPixel > 1)
    ].
    (photometric == #rgb) ifTrue:[
        colorType := ColorTypeRGB.
        ^ (samplesPerPixel > 3)
    ].
    (photometric == #rgba) ifTrue:[
        colorType := ColorTypeRGBAlpha.
        ^ (samplesPerPixel > 3)
    ].
    (photometric == #palette) ifTrue:[
        colorType := ColorTypePalette.
        ^ (samplesPerPixel > 1)
    ].
    self error:'unhandled photometric: ',photometric asString.
    ^ false.

    "Created: / 11-04-2017 / 12:39:30 / cg"
    "Modified (comment): / 31-08-2017 / 17:24:31 / cg"
!

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 nextPutInt32:len MSB:true.
    realOutStream nextPutAll:chunkBytes.
    realOutStream nextPutInt32:crc MSB:true.
!

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

writeIHDRChunk
    |hasMask bitsPerChannel|

    hasMask := self determineColorTypeAndHasMask.
    hasMask ifTrue:[
        "/ make it grayAlpha / rgba
        ((colorType == ColorTypeGray) or:[colorType == ColorTypeGray]) ifTrue:[
            colorType := colorType bitOr:4.  "/ +alpha
        ].
    ].

    "bitsperchannel"
    depth <= 8 ifTrue:[
        bitsPerChannel := depth
    ] ifFalse:[
        (colorType == ColorTypeRGB or:[colorType == ColorTypeRGBAlpha]) ifTrue:[ 
            "/ all channels must have the same nr of bits
            self assert:(bitsPerSample asSet size == 1). 
            bitsPerChannel := bitsPerSample first
        ] ifFalse:[
            bitsPerChannel := depth
        ]
    ].
    
    self 
        writeChunk: 'IHDR'
        size: (4+4+5)
        with:[ 
            outStream nextPutInt32:width MSB:true.   
            outStream nextPutInt32:height MSB:true.   
            outStream nextPut: bitsPerChannel.
            outStream nextPut: colorType.  
            outStream nextPut: 0.  "Compression"
            outStream nextPut: 0.  "Filter method"
            outStream nextPut: 0   "Non-interlaced"
        ]

    "Modified: / 04-09-2017 / 18:34:15 / cg"
!

writeImageDataChunk
    |compressedByteStream compressedBytes zlibWriter idx 
     row32 bytesPerPixel|

    bytesPerScanline := self bytesPerRow.
    
    compressedByteStream := WriteStream on:(ByteArray new:(bytesPerScanline*height)).
    zlibWriter := ZipStream writeOpenAsZipStreamOn:compressedByteStream suppressHeaderAndChecksum:false.
    zlibWriter binary.

    (mask notNil and:[photometric ~~ #palette]) ifTrue:[
        (depth == 32) ifTrue:[
            bytesPerPixel := 4
        ] ifFalse:[
            "/ for now - only support depth24 + mask
            self assert:(depth == 24).
            bytesPerPixel := 3.
        ].
        
        "/ on-the-fly place mask into the alpha channel.
        row32 := ByteArray new:(4 * width).
        self assert:(bytesPerScanline == (bytesPerPixel * width)).

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

            "/ expand rgb to rgba
            maskRow := mask rowAt:y.

            dstIdx := 1.
            1 to:width do:[:x |
                row32 at:dstIdx put:(data at:idx).
                row32 at:dstIdx+1 put:(data at:idx+1).
                row32 at:dstIdx+2 put:(data at:idx+2).
                row32 at:dstIdx+3 put:((maskRow at:x) == 0 ifTrue:[0] ifFalse:[16rFF]).
                idx := idx + bytesPerPixel.
                dstIdx := dstIdx + 4.
            ].

            zlibWriter nextPutAll:#[0].       "/ no filter
            zlibWriter nextPutAll:row32.
        ].
    ] ifFalse:[
        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
        ]

    "Modified: / 25-02-2017 / 14:27:34 / cg"
    "Modified (format): / 11-04-2017 / 12:41:22 / cg"
!

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

writeTRNSChunk
    self 
        writeChunk: 'tRNS'
        size: 1
        with:[
            outStream nextPut: paletteIndexForMaskedPixels
        ]

    "Created: / 16-02-2017 / 19:58:06 / cg"
! !

!PNGReader class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


PNGReader initialize!