[ENH] PNGReadWriter

Duane Maxwell dmaxwell at entrypoint.com
Wed Apr 19 18:31:38 UTC 2000


Change Set:		PNG
Date:			19 April 2000
Author:			Duane Maxwell, Bob Arning

This changeset implements a reader for Portable Network Graphics (PNG) files.

This is an alpha release - caveat emptor.  While it seems to read all of
the PNG test images, more testing is certainly needed.  It does little to
no error checking, and does not utilize the gamma information.  It also
doesn't yet write PNG files - this is left as an exercise for the reader.

See http://www.cdrom.com/pub/png/ for more information about PNG

Submitted by Duane Maxwell/Entrypoint
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1782] on 19 April 2000
at 11:27:28 am'!
"Change Set:		PNG
Date:			19 April 2000
Author:			Duane Maxwell, Bob Arning

This changeset implements a reader for Portable Network Graphics (PNG) files.

This is an alpha release.  While it seems to read all of the PNG test
images, more testing is needed.  It does little to no error checking, and
does not utilize the gamma information.  It also doesn't yet write PNG
files - this is left as an exercise for the reader.

See http://www.cdrom.com/pub/png/ for more information about PNG

Submitted by Duane Maxwell/Entrypoint"!

ImageReadWriter subclass: #PNGReadWriter
	instanceVariableNames: 'chunk form width height depth
bitsPerChannel colorType interlaceMethod bitsPerPixel bytesPerScanline
thisScanline prevScanline rowSize '
	classVariableNames: 'BPP BlockHeight BlockWidth IDAT IEND IHDR PLTE '
	poolDictionaries: ''
	category: 'Graphics-Files'!

!FileList methodsFor: 'file list menu' stamp: 'DSM 3/23/2000 12:07'!
itemsForFileEnding: suffix
	| labels lines selectors |
	labels _ OrderedCollection new.
	lines _ OrderedCollection new.
	selectors _ OrderedCollection new.
	(suffix = 'bmp') | (suffix = 'gif') | (suffix = 'jpg') | (suffix =
'form') | (suffix = '*') | (suffix = 'png') ifTrue:
		[labels addAll: #('open image in a window' 'read image into
ImageImports'
						 'open image as background').
		selectors addAll: #(openImageInWindow importImage
openAsBackground)].
	(suffix = 'morph') | (suffix = 'morphs') | (suffix = 'sp') |
(suffix = '*') ifTrue:
		[labels add: 'load as morph'.
		selectors add: #openMorphFromFile.
		labels add: 'load as project'.
		selectors add: #openProjectFromFile].
	(suffix = 'extseg') ifTrue:
		[labels add: 'load as project'.
		selectors add: #openProjectFromFile].
	(suffix = 'bo') | (suffix = '*') ifTrue:[
		labels add: 'load as book'.
		selectors add: #openBookFromFile].
	(suffix = 'mid') | (suffix = '*') ifTrue:
		[labels add: 'play midi file'.
		selectors add: #playMidiFile].
	(suffix = 'movie') | (suffix = '*') ifTrue:
		[labels add: 'open as movie'.
		selectors add: #openAsMovie].
	(suffix = 'st') | (suffix = 'cs') | (suffix = '*') ifTrue:
		[suffix = '*' ifTrue: [lines add: labels size].
		labels addAll: #('fileIn' 'file into new change set'
'browse changes' 'browse code' 'remove line feeds' 'broadcast as update').
		lines add: labels size - 1.
		selectors addAll: #(fileInSelection fileIntoNewChangeSet
browseChanges browseFile removeLinefeeds putUpdate)].
	(suffix = 'swf') | (suffix = '*') ifTrue:[
		labels add:'open as Flash'.
		selectors add: #openAsFlash].
	(suffix = 'ttf') | (suffix = '*') ifTrue:[
		labels add: 'open true type font'.
		selectors add: #openAsTTF].
	(suffix = 'gz') | (suffix = '*') ifTrue:[
		labels addAll: #('view decompressed' 'decompress to file').
		selectors addAll: #(viewGZipContents saveGZipContents)].
	(suffix = '3ds') | (suffix = '*') ifTrue:[
		labels add: 'Open 3DS file'.
		selectors add: #open3DSFile].
	(suffix = 'tape') | (suffix = '*') ifTrue:
		[labels add: 'open for playback'.
		selectors add: #openTapeFromFile].
	(suffix = 'wrl') | (suffix = '*') ifTrue:
		[labels add: 'open in Wonderland'.
		selectors add: #openVRMLFile].
	(suffix = '*') ifTrue:
		[labels addAll: #('generate HTML').
		lines add: labels size - 1.
		selectors addAll: #(renderFile)].
	^ Array with: labels with: lines with: selectors! !


!PNGReadWriter commentStamp: '<historical>' prior: 0!
I am a subclass of ImageReadWriter that decodes Portable Network Graphics
(PNG) images.

Submitted by Duane Maxwell!

!PNGReadWriter reorganize!
('accessing' nextImage understandsImageFormat)
('chunks' processIDATChunk processIHDRChunk processInterlaced
processNonInterlaced processPLTEChunk)
('filtering' filterAverage: filterHorizontal: filterNone: filterPaeth:
filterScanline:count: filterVertical: paethPredictLeft:above:aboveLeft:)
('pixel copies' copyPixels: copyPixels:at:by: copyPixelsGray:
copyPixelsGray:at:by: copyPixelsGrayAlpha: copyPixelsGrayAlpha:at:by:
copyPixelsIndexed: copyPixelsIndexed:at:by: copyPixelsRGB:
copyPixelsRGB:at:by: copyPixelsRGBA: copyPixelsRGBA:at:by:)
('miscellaneous' grayColorsFor:)
!


!PNGReadWriter methodsFor: 'accessing' stamp: 'RAA 3/28/2000 08:21'!
nextImage

	| length type dataChunk |

	dataChunk _ nil.
	stream reset.
	(stream respondsTo: #binary) ifTrue: [ stream binary] .
	stream skip: 8.
	[stream atEnd] whileFalse: [
		length _ self nextLong.
		type _ self nextLong.
		chunk _ self next: length.
		"crc _" self nextLong. "------------------------TODO -
validate crc"
		type = IHDR ifTrue: [self processIHDRChunk].
		type = PLTE ifTrue: [self processPLTEChunk].
		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---"
			dataChunk _ dataChunk ifNil: [chunk] ifNotNil:
[dataChunk,chunk].
		].
	].
	chunk _ dataChunk.
	self processIDATChunk.
	^ form
! !

!PNGReadWriter methodsFor: 'accessing' stamp: 'DSM 3/24/2000 01:12'!
understandsImageFormat
	#(137 80 78 71 13 10 26 10) do: [ :byte |
		stream next = byte ifFalse: [^ false]].
	^ true
! !

!PNGReadWriter methodsFor: 'chunks' stamp: 'RAA 3/28/2000 08:22'!
processIDATChunk

	interlaceMethod = 0
		ifTrue: [ self processNonInterlaced ]
		ifFalse: [ self processInterlaced ]
! !

!PNGReadWriter methodsFor: 'chunks' stamp: 'DSM 3/26/2000 21:35'!
processIHDRChunk
	width _ chunk longAt: 1 bigEndian: true.
	height _ chunk longAt: 5 bigEndian: true.
	bitsPerChannel _ chunk at: 9.
	colorType _ chunk at: 10.
	"compression _ chunk at: 11." "TODO - validate compression"
	"filterMethod _ chunk at: 12." "TODO - validate filterMethod"
	interlaceMethod _ chunk at: 13. "TODO - validate interlace method"
	(#(2 4 6) includes: colorType)
		ifTrue: [
			depth _ 32.
			form _ Form extent: width at height depth: depth
			].
	(#(0 3) includes: colorType)
		ifTrue: [
			depth _ bitsPerChannel min: 8.
			form _ ColorForm extent: width at height depth: depth.
			colorType = 0 ifTrue: [ "grayscale"
				form colors: (self grayColorsFor: depth).
				]
			].
	bitsPerPixel _ (BPP at: colorType+1) at: bitsPerChannel highBit.
	bytesPerScanline _ width * bitsPerPixel + 7 // 8.
	rowSize _ form width * form depth + 31 >> 5.
! !

!PNGReadWriter methodsFor: 'chunks' stamp: 'DSM 4/19/2000 11:13'!
processInterlaced
	| z filter bytesPerPass startingCol colIncrement rowIncrement
startingRow cx sc |

	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: chunk from: 1 to: chunk size.
	1 to: 7 do: [ :pass |
		cx _ colIncrement at: pass.
		sc _ startingCol at: pass.
		"Transcript show: 'Pass=',pass asString; cr."

		bytesPerPass _ (width - sc + cx - 1 // cx) * bitsPerPixel +
7 // 8.
		prevScanline _ ByteArray new: bytesPerPass.
		(startingRow at: pass) to: height-1 by: (rowIncrement at:
pass) do: [ :y |
			filter _ z next. "TODO - validate filter"
			thisScanline _ z next: bytesPerPass.
			"Transcript show: 'y=',y asString,' ',thisScanline
asExplorerString; cr."
			self filterScanline: filter count: bytesPerPass.
			self copyPixels: y at: sc by: cx.
			prevScanline replaceFrom: 1 to: bytesPerPass with:
thisScanline startingAt: 1
			]
		]
! !

!PNGReadWriter methodsFor: 'chunks' stamp: 'DSM 3/26/2000 21:35'!
processNonInterlaced
	| z filter |
	z _ ZLibReadStream on: chunk from: 1 to: chunk size.
	prevScanline _ ByteArray new: bytesPerScanline.
	0 to: height-1 do: [ :y |
		filter _ z next. "TODO - validate filter"
		thisScanline _ z next: bytesPerScanline.
		self filterScanline: filter count: bytesPerScanline.
		self copyPixels: y.
		prevScanline replaceFrom: 1 to: bytesPerScanline with:
thisScanline startingAt: 1
		]
! !

!PNGReadWriter methodsFor: 'chunks' stamp: 'DSM 3/26/2000 22:33'!
processPLTEChunk
	| colorCount colors i |
	colorCount _ chunk size // 3. "TODO - validate colorCount against
depth"
	colors _ Array new: colorCount.
	0 to: colorCount-1 do: [ :index |
		i _ index * 3 + 1.
		colors at: index+1 put:
			(Color r: (chunk at: i)/255 g: (chunk at: i+1)/255 b: (chunk at: i+2)/255)
		].
	form colors: colors
! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:53'!
filterAverage: count
	"Use the average of the pixel to the left and the pixel above as a
predictor"

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

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:54'!
filterHorizontal: count
	"Use the pixel to the left as a predictor"

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


! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:55'!
filterNone: count
! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:54'!
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 this left above aboveLeft |
	delta _ 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 |
		this _ thisScanline at: i.
		left _ thisScanline at: i-delta.
		above _ prevScanline at: i.
		aboveLeft _ prevScanline at: i-delta.
		thisScanline at: i put:
		((this + (self paethPredictLeft: left above: above
aboveLeft: aboveLeft)) bitAnd: 255) ]

! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:55'!
filterScanline: filterType count: count
	| filter |
	filter _ #(filterNone: filterHorizontal: filterVertical:
filterAverage: filterPaeth:)
		at: filterType+1.
	self perform: filter asSymbol with: count.

! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/25/2000 17:54'!
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) ]

! !

!PNGReadWriter methodsFor: 'filtering' stamp: 'DSM 3/24/2000 23:25'!
paethPredictLeft: a above: b aboveLeft: c
	"Predicts the value of a pixel based on nearby pixels, based on
Paeth (GG II, 1991)"

	| p pa pb pc |
	p _ a + b - c .
	pa _ (p - a) abs.
	pb _ (p - b) abs.
	pc _ (p - c) abs.
	((pa <= pb) and: [pa <= pc]) ifTrue: [^ a].
	(pb <= pc) ifTrue: [^ b].
	^ c
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:32'!
copyPixels: y
	"Handle non-interlaced pixels of supported colorTypes"

	| s |
	s _ #(copyPixelsGray: nil copyPixelsRGB: copyPixelsIndexed:
		  copyPixelsGrayAlpha: nil copyPixelsRGBA:) at: colorType+1.
	self perform: s asSymbol with: y
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:30'!
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 asSymbol with: y with: startX with: incX
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:31'!
copyPixelsGray: y
	"Handle non-interlaced grayscale color mode (colorType = 0)"

	| b offset |
	bitsPerChannel = 16
		ifTrue: [
			b _ BitBlt bitPokerToForm: form.
			0 to: width-1 do: [ :x |
				b pixelAt: x at y put: 255 - (thisScanline at:
(x<<1)+1).
				].
			^ self
			]
		ifFalse: [
			offset _ y*rowSize+1.
			b _ form bits.
			0 to: rowSize-1 do: [ :i |
				b at: offset+i put: (thisScanline
unsignedLongAt: i<<2+1 bigEndian: true)].
			^ self
			]

! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'RAA 3/28/2000 06:46'!
copyPixelsGray: y at: startX by: incX
	"Handle interlaced grayscale color mode (colorType = 0)"

	| b offset bits w pixel mask blitter pixelNumber pixPerByte rawByte
shifts |
	bitsPerChannel = 16
		ifTrue: [
			b _ BitBlt bitPokerToForm: form.
			startX to: width-1 by: incX do: [ :x |
				b pixelAt: x at y put: 255 - (thisScanline at:
(x//incX<<1)+1).
				].
			^ self
			].
	offset _ y*rowSize+1.
	bits _ form bits.
	bitsPerChannel = 8 ifTrue: [
		startX to: width-1 by: incX do: [ :x |
			w _ offset + (x>>2).
			b _ 3- (x \\ 4) * 8.
			pixel _ (thisScanline at: x // incX + 1)<<b.
			mask _ (255<<b) bitInvert32.
			bits at: w put: (((bits at: w) bitAnd: mask) bitOr:
pixel)
		].
		^ self
	].
	bitsPerChannel = 1 ifTrue: [
		pixPerByte _ 8.
		mask _ 1.
		shifts _ #(7 6 5 4 3 2 1 0).
	].
	bitsPerChannel = 2 ifTrue: [
		pixPerByte _ 4.
		mask _ 3.
		shifts _ #(6 4 2 0).
	].
	bitsPerChannel = 4 ifTrue: [
		pixPerByte _ 2.
		mask _ 15.
		shifts _ #(4 0).
	].

	blitter _ BitBlt bitPokerToForm: form.
	pixelNumber _ 0.
	startX to: width-1 by: incX do: [ :x |
		rawByte _ thisScanline at: (pixelNumber // pixPerByte) + 1.
		pixel _ (rawByte >> (shifts at: (pixelNumber \\ pixPerByte)
+ 1)) bitAnd: mask.
		blitter pixelAt: (x at y) put: pixel.
		pixelNumber _ pixelNumber + 1.
	].
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:31'!
copyPixelsGrayAlpha: y
	"Handle non-interlaced grayscale with alpha color mode (colorType = 4)"

	| i pixel gray b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			0 to: width-1 do: [ :x |
				i _ (x << 1) + 1.
				gray _ thisScanline at: i.
				pixel _ ((thisScanline at: i+1)<<24)
					+ (gray<<16) + (gray<<8) + gray.
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			0 to: width-1 do: [ :x |
				i _ (x << 2) + 1.
				gray _ thisScanline at: i.
				pixel _ ((thisScanline at: i+2)<<24)
					+ (gray<<16) + (gray<<8) + gray.
				b pixelAt: x at y put: pixel.
				]
			]
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:30'!
copyPixelsGrayAlpha: y at: startX by: incX
	"Handle interlaced grayscale with alpha color mode (colorType = 4)"

	| i pixel gray b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX << 1) + 1.
				gray _ thisScanline at: i.
				pixel _ ((thisScanline at: i+1)<<24)
					+ (gray<<16) + (gray<<8) + gray.
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX << 2) + 1.
				gray _ thisScanline at: i.
				pixel _ ((thisScanline at: i+2)<<24)
					+ (gray<<16) + (gray<<8) + gray.
				b pixelAt: x at y put: pixel.
				]
			]
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:31'!
copyPixelsIndexed: y
	"Handle non-interlaced indexed color mode (colorType = 3)"

	| offset |
	offset _ y*rowSize+1.
	0 to: rowSize-1 do: [ :i |
		form bits at: offset+i put: (thisScanline unsignedLongAt:
i<<2+1 bigEndian: true)].! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'RAA 3/28/2000 06:46'!
copyPixelsIndexed: y at: startX by: incX
	"Handle interlaced indexed color mode (colorType = 3)"

	| offset b bits w pixel mask pixPerByte shifts blitter pixelNumber
rawByte |
	offset _ y*rowSize+1.
	bits _ form bits.
	bitsPerChannel = 8
		ifTrue: [
			startX to: width-1 by: incX do: [ :x |
				w _ offset + (x>>2).
				b _ 3 - (x \\ 4) * 8.
				pixel _ (thisScanline at: x // incX + 1)<<b.
				mask _ (255<<b) bitInvert32.
				bits at: w put: (((bits at: w) bitAnd:
mask) bitOr: pixel)].
			^ self ].
	bitsPerChannel = 1 ifTrue: [
		pixPerByte _ 8.
		mask _ 1.
		shifts _ #(7 6 5 4 3 2 1 0).
	].
	bitsPerChannel = 2 ifTrue: [
		pixPerByte _ 4.
		mask _ 3.
		shifts _ #(6 4 2 0).
	].
	bitsPerChannel = 4 ifTrue: [
		pixPerByte _ 2.
		mask _ 15.
		shifts _ #(4 0).
	].

	blitter _ BitBlt bitPokerToForm: form.
	pixelNumber _ 0.
	startX to: width-1 by: incX do: [ :x |
		rawByte _ thisScanline at: (pixelNumber // pixPerByte) + 1.
		pixel _ (rawByte >> (shifts at: (pixelNumber \\ pixPerByte)
+ 1)) bitAnd: mask.
		blitter pixelAt: (x at y) put: pixel.
		pixelNumber _ pixelNumber + 1.
	].
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:31'!
copyPixelsRGB: y
	"Handle non-interlaced RGB color mode (colorType = 2)"

	| i pixel b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			0 to: width-1 do: [ :x |
				i _ (x * 3) + 1.
				pixel _ 16rFF000000
				     + ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+1)<<8)
					+ ((thisScanline at: i+2)).
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			0 to: width-1 do: [ :x |
				i _ (x * 6) + 1.
				pixel _ 16rFF000000
					+  ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+2)<<8)
					+ ((thisScanline at: i+4)).
				b pixelAt: x at y put: pixel.
				]
			]

! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:30'!
copyPixelsRGB: y at: startX by: incX
	"Handle interlaced RGB color mode (colorType = 2)"

	| i pixel b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX * 3) + 1.
				pixel _ 16rFF000000
				     + ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+1)<<8)
					+ ((thisScanline at: i+2)).
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX * 6) + 1.
				pixel _ 16rFF000000
					+  ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+2)<<8)
					+ ((thisScanline at: i+4)).
				b pixelAt: x at y put: pixel.
				]
			]

! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:30'!
copyPixelsRGBA: y
	"Handle non-interlaced RGBA color modes (colorType = 6)"

	| i pixel b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			0 to: width-1 do: [ :x |
				i _ (x << 2) + 1.
				pixel _ ((thisScanline at: i+3)<<24)
					+ ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+1)<<8)
					+ ((thisScanline at: i+2)).
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			0 to: width-1 do: [ :x |
				i _ (x << 3) +1.
				pixel _ ((thisScanline at: i+6)<<24)
					+  ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+2)<<8)
					+ ((thisScanline at: i+4)).
				b pixelAt: x at y put: pixel
				]
			]
! !

!PNGReadWriter methodsFor: 'pixel copies' stamp: 'DSM 3/26/2000 21:30'!
copyPixelsRGBA: y at: startX by: incX
	"Handle interlaced RGBA color modes (colorType = 6)"

	| i pixel b |
	b _ BitBlt bitPokerToForm: form.
	bitsPerChannel = 8
		ifTrue: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX << 2) + 1.
				pixel _ ((thisScanline at: i+3)<<24)
					+ ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+1)<<8)
					+ ((thisScanline at: i+2)).
				b pixelAt: x at y put: pixel.
				]
			]
		ifFalse: [
			startX to: width-1 by: incX do: [ :x |
				i _ (x // incX << 3) +1.
				pixel _ ((thisScanline at: i+6)<<24)
					+  ((thisScanline at: i)<<16)
					+ ((thisScanline at: i+2)<<8)
					+ ((thisScanline at: i+4)).
				b pixelAt: x at y put: pixel
				]
			]
! !

!PNGReadWriter methodsFor: 'miscellaneous' stamp: 'DSM 3/24/2000 23:28'!
grayColorsFor: d
	"return a color table for a gray image"

	| colors |
	colors _ Array new: 1<<d.
	d = 1 ifTrue: [
		colors at: 1 put: Color black.
		colors at: 2 put: Color white.
		^ colors
		].
	d = 2 ifTrue: [
		colors at: 1 put: Color black.
		colors at: 2 put: (Color gray: 0.3333).
		colors at: 3 put: (Color gray: 0.6667).
		colors at: 4 put: Color white.
		^ colors.
		].
	d = 4 ifTrue: [
		0 to: 15 do: [ :g |
			colors at: g+1 put: (Color gray: (g/15) asFloat) ].
		^ colors
		].
	d = 8 ifTrue: [
		0 to: 255 do: [ :g |
			colors at: g+1 put: (Color gray: (g/255) asFloat) ].
		^ colors
		].
! !


!PNGReadWriter class methodsFor: 'as yet unclassified' stamp: 'RAA
3/28/2000 06:31'!
initialize
	"
	PNGReadWriter initialize
	"
	IHDR _ 'IHDR' asPacked.
	IEND _ 'IEND' asPacked.
	PLTE _ 'PLTE' asPacked.
	IDAT _ 'IDAT' asPacked.

	BPP _ {	#(1 2 4 8 16).
			#(0 0 0 0 0).
			#(0 0 0 24 48).
			#(1 2 4 8 0).
			#(0 0 0 16 32).
			#(0 0 0 0 0).
			#(0 0 0 32 64).
			#(0 0 0 0 0) }.

	BlockHeight _ #(8 8 4 4 2 2 1).
	BlockWidth _ #(8 4 4 2 2 1 1)
! !


PNGReadWriter initialize!


More information about the Squeak-dev mailing list