[squeak-dev] The Trunk: Graphics-ul.275.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 25 15:06:16 UTC 2013


Levente Uzonyi uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-ul.275.mcz

==================== Summary ====================

Name: Graphics-ul.275
Author: ul
Time: 25 October 2013, 5:02:25.178 pm
UUID: faacabb7-52fd-4834-8efa-be646e21ef4c
Ancestors: Graphics-nice.274

Speed up reading of large png images:
- avoid unnecessary allocations in #processNextChunk, by collecting the data from the IDAT chunks into a WriteStream
- reuse the existing ByteArray if the next chunk has the same size as the previous in #processNextChunk
- reuse the contents of the idatChunkStream in #processNonInterlaced and #processInterlaced
- speed up #copyPixelsRGB: a bit by using a ByteArray as the bits for the Form, just like in #copyPixelsRGBA:.

=============== Diff against Graphics-nice.274 ===============

Item was changed:
  ImageReadWriter subclass: #PNGReadWriter
+ 	instanceVariableNames: 'chunk form width height depth backColor bitsPerChannel colorType interlaceMethod bitsPerPixel bytesPerScanline thisScanline prevScanline rowSize idatChunkStream unknownChunks palette transparentPixelValue filtersSeen swizzleMap cachedDecoderMap bigEndian'
- 	instanceVariableNames: 'chunk form width height depth backColor bitsPerChannel colorType interlaceMethod bitsPerPixel bytesPerScanline thisScanline prevScanline rowSize globalDataChunk unknownChunks palette transparentPixelValue filtersSeen swizzleMap cachedDecoderMap bigEndian'
  	classVariableNames: 'BPP BlockHeight BlockWidth Debugging StandardColors StandardSwizzleMaps'
  	poolDictionaries: ''
  	category: 'Graphics-Files'!
  
  !PNGReadWriter commentStamp: '<historical>' prior: 0!
  I am a subclass of ImageReadWriter that decodes Portable Network Graphics
  (PNG) images.
  
  Submitted by Duane Maxwell!

Item was changed:
  ----- Method: PNGReadWriter>>copyPixelsRGB: (in category 'pixel copies') -----
  copyPixelsRGB: y
  	"Handle non-interlaced RGB color mode (colorType = 2)"
  
  	| i pixel tempForm tempBits |
+ 	(transparentPixelValue isNil and: [ bitsPerChannel = 8 ]) ifTrue: [ "Do the same trick as in #copyPixelsRGBA:"
+ 		| targetIndex |
+ 		tempBits := ByteArray new: thisScanline size * 4 // 3 withAll: 16rFF.
+ 		tempForm := Form extent: width at 1 depth: 32 bits: tempBits.
+ 		targetIndex := 1.
+ 		1 to: thisScanline size by: 3 do: [ :index |
+ 			tempBits
+ 				at: targetIndex put: (thisScanline at: index);
+ 				at: targetIndex + 1 put: (thisScanline at: index + 1);
+ 				at: targetIndex + 2 put: (thisScanline at: index + 2).
+ 			targetIndex := targetIndex + 4 ].
+ 		cachedDecoderMap 
+ 			ifNil:[cachedDecoderMap := self rgbaDecoderMapForDepth: depth].
+ 		(BitBlt toForm: form)
+ 			sourceForm: tempForm;
+ 			destOrigin: 0 at y;
+ 			combinationRule: Form over;
+ 			colorMap: cachedDecoderMap;
+ 			copyBits.
+ 		^self ].
- 
  	tempForm := Form extent: width at 1 depth: 32.
  	tempBits := tempForm bits.
  	pixel := LargePositiveInteger new: 4.
  	pixel at: 4 put: 16rFF.
  	bitsPerChannel = 8 ifTrue: [
  		i := 1.
  		1 to: width do: [ :x |
  			pixel
  				at: 3 put: (thisScanline at: i);
  				at: 2 put: (thisScanline at: i+1);
  				at: 1 put: (thisScanline at: i+2).
  			tempBits at: x put: pixel.
  			i := i + 3.
  		]
  	] ifFalse: [
  		i := 1.
  		1 to: width do: [ :x |
  			pixel
  				at: 3 put: (thisScanline at: i);
  				at: 2 put: (thisScanline at: i+2);
  				at: 1 put: (thisScanline at: i+4).
  			tempBits at: x put: pixel.
  			i := i + 6.
  		]
  	].
  	transparentPixelValue ifNotNil: [
  		1 to: width do: [ :x |
  			(tempBits at: x) = transparentPixelValue ifTrue: [
  				tempBits at: x put: 0.
  			].
  		].
  	].
  	tempForm displayOn: form at: 0 at y rule: Form paint.
  !

Item was changed:
  ----- Method: PNGReadWriter>>nextImage (in category 'accessing') -----
  nextImage
  	bigEndian := Smalltalk isBigEndian.
  	filtersSeen := Bag new.
+ 	idatChunkStream := nil.
- 	globalDataChunk := nil.
  	transparentPixelValue := nil.
  	unknownChunks := Set new.
  	stream reset.
  	stream binary.
  	stream skip: 8.
  	[stream atEnd] whileFalse: [self processNextChunk].
  	"Set up our form"
  	palette ifNotNil: 
  			["Dump the palette if it's the same as our standard palette"
  
  			palette = (StandardColors copyFrom: 1 to: palette size) 
  				ifTrue: [palette := nil]].
  	(depth <= 8 and: [palette notNil]) 
  		ifTrue: 
  			[form := ColorForm extent: width @ height depth: depth.
  			form colors: palette]
  		ifFalse: [form := Form extent: width @ height depth: depth].
  	backColor ifNotNil: [form fillColor: backColor].
+ 	idatChunkStream 
+ 		ifNil: [ self error: 'image data is missing' ]
+ 		ifNotNil: [ self processIDATChunk ].
- 	chunk := globalDataChunk ifNil: [self error: 'image data is missing'].
- 	chunk ifNotNil: [self processIDATChunk].
  	unknownChunks isEmpty 
  		ifFalse: 
  			["Transcript show: ' ',unknownChunks asSortedCollection asArray printString."
  
  			].
  	self debugging 
  		ifTrue: 
  			[Transcript
  				cr;
  				show: 'form = ' , form printString.
  			Transcript
  				cr;
  				show: 'colorType = ' , colorType printString.
  			Transcript
  				cr;
  				show: 'interlaceMethod = ' , interlaceMethod printString.
  			Transcript
  				cr;
  				show: 'filters = ' , filtersSeen sortedCounts asArray printString].
  	^form!

Item was changed:
  ----- Method: PNGReadWriter>>processInterlaced (in category 'chunks') -----
  processInterlaced
  	| z startingCol colIncrement rowIncrement startingRow |
  	startingCol := #(0 4 0 2 0 1 0 ).
  	colIncrement := #(8 8 4 4 2 2 1 ).
  	rowIncrement := #(8 8 8 4 4 2 2 ).
  	startingRow := #(0 0 4 0 2 0 1 ).
+ 	z := ZLibReadStream 
+ 		on: idatChunkStream originalContents
+ 		from: 1
+ 		to: idatChunkStream position.
- 	z := ZLibReadStream on: chunk from: 1 to: chunk size.
  	1 to: 7 do: [:pass |
  		| cx sc bytesPerPass |
  		(self doPass: pass)
  			ifTrue:
  				[cx := colIncrement at: pass.
  				sc := startingCol 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: (rowIncrement at: pass)
  					do: [:y |
  						| filter temp |
  						filter := z next.
  						filtersSeen add: filter.
  						(filter isNil or: [(filter between: 0 and: 4) not])
  							ifTrue: [^ self].
  						thisScanline := z next: bytesPerPass into: thisScanline startingAt: 1.
  						self filterScanline: filter count: bytesPerPass.
  						self copyPixels: y at: sc by: cx.
  						temp := prevScanline.
  						prevScanline := thisScanline.
  						thisScanline := temp.
  					]
  				]
  	].
  	z atEnd ifFalse:[self error:'Unexpected data'].!

Item was changed:
  ----- Method: PNGReadWriter>>processNextChunk (in category 'chunks') -----
  processNextChunk
  
  	| length chunkType crc chunkCrc |
  
  	length := self nextLong.
  
  	chunkType := (self next: 4) asString.
+ 	(chunk isNil or: [ chunk size ~= length ])
+ 		ifTrue: [ chunk := self next: length ]
+ 		ifFalse: [ stream next: length into: chunk startingAt: 1 ].
- 	chunk := self next: length.
  	chunkCrc := self nextLong bitXor: 16rFFFFFFFF.
  	crc := self updateCrc: 16rFFFFFFFF from: 1 to: 4 in: chunkType.
  	crc := self updateCrc: crc from: 1 to: length in: chunk.
  	crc = chunkCrc ifFalse:[
  		self error: 'PNGReadWriter crc error in chunk ', chunkType.
  	].
  
  	chunkType = 'IEND' ifTrue: [^self	"*should* be the last chunk"].
  	chunkType = 'sBIT' ifTrue: [^self processSBITChunk "could indicate unusual sample depth in original"].
  	chunkType = 'gAMA' ifTrue: [^self 	"indicates gamma correction value"].
  	chunkType = 'bKGD' ifTrue: [^self processBackgroundChunk].
  	chunkType = 'pHYs' ifTrue: [^self processPhysicalPixelChunk].
  	chunkType = 'tRNS' ifTrue: [^self processTransparencyChunk].
  
  	chunkType = 'IHDR' ifTrue: [^self processIHDRChunk].
  	chunkType = 'PLTE' ifTrue: [^self processPLTEChunk].
  	chunkType = '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---"
+ 		idatChunkStream
+ 			ifNil: [ idatChunkStream := WriteStream with: chunk copy ]
+ 			ifNotNil: [ idatChunkStream nextPutAll: chunk ].
- 		globalDataChunk := globalDataChunk ifNil: [chunk] ifNotNil:
- 			[globalDataChunk,chunk].
  		^self
  	].
  	unknownChunks add: chunkType.
  !

Item was changed:
  ----- Method: PNGReadWriter>>processNonInterlaced (in category 'chunks') -----
  processNonInterlaced
  	| z filter temp copyMethod debug |
  	debug := self debugging.
  	copyMethod := #(copyPixelsGray: nil copyPixelsRGB: copyPixelsIndexed:
  		  copyPixelsGrayAlpha: nil copyPixelsRGBA:) at: colorType+1.
+ 	debug ifTrue: [ Transcript cr; nextPutAll: 'NI chunk size='; print: idatChunkStream position ].
+ 	z := ZLibReadStream 
+ 		on: idatChunkStream originalContents
+ 		from: 1
+ 		to: idatChunkStream position.
- 	debug ifTrue: [ Transcript cr; nextPutAll: 'NI chunk size='; print: chunk size ].
- 	z := ZLibReadStream on: chunk from: 1 to: chunk size.
  	prevScanline := ByteArray new: bytesPerScanline.
  	thisScanline := ByteArray new: bytesPerScanline.
  	0 to: height-1 do: [ :y |
+ 		filter := z next.
- 		filter := (z next: 1) first.
  		debug ifTrue:[filtersSeen add: filter].
  		thisScanline := z next: bytesPerScanline into: thisScanline startingAt: 1.
  		(debug and: [ thisScanline size < bytesPerScanline ]) ifTrue: [ Transcript nextPutAll: ('wanted {1} but only got {2}' format: { bytesPerScanline. thisScanline size }); cr ].
  		filter = 0 ifFalse:[self filterScanline: filter count: bytesPerScanline].
  		self perform: copyMethod with: y.
  		temp := prevScanline.
  		prevScanline := thisScanline.
  		thisScanline := temp.
  		].
  	z atEnd ifFalse:[self error:'Unexpected data'].
  	debug ifTrue: [Transcript  nextPutAll: ' compressed size='; print: z position  ].
  !



More information about the Squeak-dev mailing list