X Bitmap support for Scamper

William Cattey wdc at mit.edu
Mon Feb 1 07:28:47 UTC 1999


I hope I'm not gonna embarass myself too much publicly circulating my
first real Smalltalk subclass.

This subclass teaches ImageReadWriter to read X bitmaps.
This would be useful, for example, if you used Scamper to look at
an MIT home directory through our school-wide web.mit.edu.
For Example: http://web.mit.edu/wdc/www/.

The MIT web server pushes back a bunch of pretty file icons
that are in X bitmap format that Scamper, until now, just
complained about.

Here is the class definition.  I'd welcome any off-list replies
telling me style things I should do differently, or code
improvements. 

Special thanks to Paul Boutin who wrote the X Bitmap Parser
in C for the Andrew Toolkit when he worked for me ~5 years ago.
I used his most excellent code as the basis for this work,
and to show me how to do X Bitmap parsing.

-wdc
'From Squeak 2.3 of January 14, 1999 on 1 February 1999 at 7:16:31 am'!
ImageReadWriter subclass: #XBMReadWriter
	instanceVariableNames: 'width height '
	classVariableNames: 'Flipbits '
	poolDictionaries: ''
	category: 'Graphics-Files'!

!XBMReadWriter methodsFor: 'private' stamp: 'wdc 2/1/1999 06:06'!
parseByteValue
	"skip over separators and return next bytevalue parsed as
	a C language number: 
		0ddd is an octal digit.
		0xddd is a hex digit.
		ddd is decimal."

	| source mybase |
	stream skipSeparators.
	source _ ReadWriteStream on: String new.
	[(stream atEnd) or: [ stream peek isSeparator ]] whileFalse: [
		source nextPut: (self next asUppercase).
	].
	mybase _ 10. "Base 10 default"
	source reset.
	(source peek = $0) ifTrue: [
		mybase _ 8.
		source next.
		(source peek = $X) ifTrue: [
			mybase _ 16.
			source next.]
	].

	^ Integer readFrom: source base: mybase.
! !

!XBMReadWriter methodsFor: 'private' stamp: 'wdc 2/1/1999 05:26'!
readHeader
	"Set width and height, and position stream at start of bytes"
	| number source setwidth setheight |

	setwidth _ setheight _ false.
	
	[((stream atEnd) or: [setwidth and: [setheight]])] whileFalse: [
		stream skipSeparators.
		(stream nextMatchAll: '#define ') ifFalse: [^ false].
		(stream skipTo: $_) ifFalse: [^ false].

		source _ WriteStream on: String new.
		[(stream atEnd) or: [ stream peek isSeparator ]] whileFalse: [
			source nextPut: (self next).
		].

		(source contents asString = 'width') ifTrue: [
			stream skipSeparators.
			number _ Integer readFrom: stream.
			(number > 0) ifTrue: [setwidth _true].
			width _ number.].

		(source contents asString = 'height') ifTrue: [
			stream skipSeparators.
			number _ Integer readFrom: stream.
			(number > 0) ifTrue: [setheight _ true].
			height _ number.].
	].

	(setwidth and: [setheight]) ifFalse: [^ false].
	
	^ (stream skipTo: ${)
! !


!XBMReadWriter methodsFor: 'accessing' stamp: 'wdc 2/1/1999 07:15'!
nextImage
	"Read in the next xbm image from the stream."

	| form long incount chunks byteWidth pad fourway outcount total |
	stream reset.
	stream ascii.
	self readHeader.
	form _ ColorForm extent: width at height depth: 1.

	incount _ 0.
	outcount _1.
	chunks _ Array new: 4.
	byteWidth _ width + 7 // 8.
	total _ byteWidth * height.
	byteWidth > 4 ifTrue: [ pad _ byteWidth \\ 4]
		ifFalse: [ pad _ 4 - byteWidth ].

	fourway _ 0.

	[(incount = total)] whileFalse: [
		incount _ incount + 1.
		fourway _ fourway + 1.

		chunks at: fourway put: (Flipbits at: ((self parseByteValue) +1)).

		(pad > 0 and: [(incount \\ byteWidth) = 0]) ifTrue: [
			1 to: pad do:
				[:q |
				fourway _ fourway + 1.
				chunks at: fourway put: 0]
		].

		fourway = 4 ifTrue: [
			long _ Integer
				byte1: (chunks at: 4)
				byte2: (chunks at: 3)
				byte3: (chunks at: 2)
				byte4: (chunks at: 1).
			(form bits) at: outcount put: long.
			fourway _ 0.
			outcount _ outcount + 1].
		].

	^ form
 ! !

!XBMReadWriter methodsFor: 'accessing' stamp: 'wdc 2/1/1999 06:20'!
understandsImageFormat
	"Test to see if the image stream format is understood by this decoder.
	This should be implemented in each subclass of ImageReadWriter so that
	a proper decoder can be selected without ImageReadWriter having to know
	about all possible image file types."
	| first |
	first _ (stream next: 7) asString.
	^ (first = '#define')
! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

XBMReadWriter class
	instanceVariableNames: ''!

!XBMReadWriter class methodsFor: 'class initialization' stamp: 'wdc 1/28/1999 02:02'!
initialize
	"XBMReadWriter initialize"

	Flipbits _ #(
	16r00 16r80 16r40 16rC0 16r20 16rA0 16r60 16rE0 16r10 16r90 16r50 16rD0 16r30 16rB0 16r70 16rF0	
	16r08 16r88 16r48 16rC8 16r28 16rA8 16r68 16rE8 16r18 16r98 16r58 16rD8 16r38 16rB8 16r78 16rF8	
	16r04 16r84 16r44 16rC4 16r24 16rA4 16r64 16rE4 16r14 16r94 16r54 16rD4 16r34 16rB4 16r74 16rF4	
	16r0C 16r8C 16r4C 16rCC 16r2C 16rAC 16r6C 16rEC 16r1C 16r9C 16r5C 16rDC 16r3C 16rBC 16r7C 16rFC	
	16r02 16r82 16r42 16rC2 16r22 16rA2 16r62 16rE2 16r12 16r92 16r52 16rD2 16r32 16rB2 16r72 16rF2	
	16r0A 16r8A 16r4A 16rCA 16r2A 16rAA 16r6A 16rEA 16r1A 16r9A 16r5A 16rDA 16r3A 16rBA 16r7A 16rFA	
	16r06 16r86 16r46 16rC6 16r26 16rA6 16r66 16rE6 16r16 16r96 16r56 16rD6 16r36 16rB6 16r76 16rF6	
	16r0E 16r8E 16r4E 16rCE 16r2E 16rAE 16r6E 16rEE 16r1E 16r9E 16r5E 16rDE 16r3E 16rBE 16r7E 16rFE	
	16r01 16r81 16r41 16rC1 16r21 16rA1 16r61 16rE1 16r11 16r91 16r51 16rD1 16r31 16rB1 16r71 16rF1	
	16r09 16r89 16r49 16rC9 16r29 16rA9 16r69 16rE9 16r19 16r99 16r59 16rD9 16r39 16rB9 16r79 16rF9	
	16r05 16r85 16r45 16rC5 16r25 16rA5 16r65 16rE5 16r15 16r95 16r55 16rD5 16r35 16rB5 16r75 16rF5	
	16r0D 16r8D 16r4D 16rCD 16r2D 16rAD 16r6D 16rED 16r1D 16r9D 16r5D 16rDD 16r3D 16rBD 16r7D 16rFD	
	16r03 16r83 16r43 16rC3 16r23 16rA3 16r63 16rE3 16r13 16r93 16r53 16rD3 16r33 16rB3 16r73 16rF3	
	16r0B 16r8B 16r4B 16rCB 16r2B 16rAB 16r6B 16rEB 16r1B 16r9B 16r5B 16rDB 16r3B 16rBB 16r7B 16rFB	
	16r07 16r87 16r47 16rC7 16r27 16rA7 16r67 16rE7 16r17 16r97 16r57 16rD7 16r37 16rB7 16r77 16rF7	
	16r0F 16r8F 16r4F 16rCF 16r2F 16rAF 16r6F 16rEF 16r1F 16r9F 16r5F 16rDF 16r3F 16rBF 16r7F 16rFF
	).! !


XBMReadWriter initialize!





More information about the Squeak-dev mailing list