[Pkg] The Trunk: Graphics-dtl.151.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Oct 24 17:01:15 UTC 2010


David T. Lewis uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-dtl.151.mcz

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

Name: Graphics-dtl.151
Author: dtl
Time: 24 October 2010, 12:57:55.652 pm
UUID: dc7bd744-10b2-457e-9213-692344a446aa
Ancestors: Graphics-nice.150

Use pragma declarations in methods that are translated to C in MiscPrimitivePlugin. Supports removal of Object>>inline: and Object>>var:declareC: from trunk.

=============== Diff against Graphics-nice.150 ===============

Item was changed:
  ----- Method: Bitmap>>compress:toByteArray: (in category 'filing') -----
  compress: bm toByteArray: ba
  	"Store a run-coded compression of the receiver into the byteArray ba,
  	and return the last index stored into. ba is assumed to be large enough.
  	The encoding is as follows...
  		S {N D}*.
  		S is the size of the original bitmap, followed by run-coded pairs.
  		N is a run-length * 4 + data code.
  		D, the data, depends on the data code...
  			0	skip N words, D is absent
  			1	N words with all 4 bytes = D (1 byte)
  			2	N words all = D (4 bytes)
  			3	N words follow in D (4N bytes)
  		S and N are encoded as follows...
  			0-223	0-223
  			224-254	(0-30)*256 + next byte (0-7935)
  			255		next 4 bytes"		
  	| size k word j lowByte eqBytes i |
  	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin'>
+ 	<var: #bm declareC: 'int *bm'>
+ 	<var: #ba declareC: 'unsigned char *ba'>
- 	self var: #bm declareC: 'int *bm'.
- 	self var: #ba declareC: 'unsigned char *ba'.
  	size := bm size.
  	i := self encodeInt: size in: ba at: 1.
  	k := 1.
  	[k <= size] whileTrue:
  		[word := bm at: k.
  		lowByte := word bitAnd: 16rFF.
  		eqBytes := ((word >> 8) bitAnd: 16rFF) = lowByte
  				and: [((word >> 16) bitAnd: 16rFF) = lowByte
  				and: [((word >> 24) bitAnd: 16rFF) = lowByte]].
  		j := k.
  		[j < size and: [word = (bm at: j+1)]]  "scan for = words..."
  			whileTrue: [j := j+1].
  		j > k ifTrue:
  			["We have two or more = words, ending at j"
  			eqBytes
  				ifTrue: ["Actually words of = bytes"
  						i := self encodeInt: j-k+1*4+1 in: ba at: i.
  						ba at: i put: lowByte.  i := i+1]
  				ifFalse: [i := self encodeInt: j-k+1*4+2 in: ba at: i.
  						i := self encodeBytesOf: word in: ba at: i].
  			k := j+1]
  			ifFalse:
  			["Check for word of 4 = bytes"
  			eqBytes ifTrue:
  				["Note 1 word of 4 = bytes"
  				i := self encodeInt: 1*4+1 in: ba at: i.
  				ba at: i put: lowByte.  i := i+1.
  				k := k + 1]
  				ifFalse:
  				["Finally, check for junk"
  				[j < size and: [(bm at: j) ~= (bm at: j+1)]]  "scan for ~= words..."
  					whileTrue: [j := j+1].
  				j = size ifTrue: [j := j + 1].
  				"We have one or more unmatching words, ending at j-1"
  				i := self encodeInt: j-k*4+3 in: ba at: i.
  				k to: j-1 do:
  					[:m | i := self encodeBytesOf: (bm at: m) in: ba at: i].
  				k := j]]].
  	^ i - 1  "number of bytes actually stored"
  "
  Space check:
   | n rawBytes myBytes b |
  n := rawBytes := myBytes := 0.
  Form allInstancesDo:
  	[:f | f unhibernate.
  	b := f bits.
  	n := n + 1.
  	rawBytes := rawBytes + (b size*4).
  	myBytes := myBytes + (b compressToByteArray size).
  	f hibernate].
  Array with: n with: rawBytes with: myBytes
  ColorForms: (116 230324 160318 )
  Forms: (113 1887808 1325055 )
  
  Integerity check:
  Form allInstances do:
  	[:f | f unhibernate.
  	f bits = (Bitmap decompressFromByteArray: f bits compressToByteArray)
  		ifFalse: [self halt].
  	f hibernate]
  
  Speed test:
  MessageTally spyOn: [Form allInstances do:
  	[:f | Bitmap decompressFromByteArray: f bits compressToByteArray]]
  "!

Item was changed:
  ----- Method: Bitmap>>decompress:fromByteArray:at: (in category 'filing') -----
  decompress: bm fromByteArray: ba at: index
  	"Decompress the body of a byteArray encoded by compressToByteArray (qv)...
  	The format is simply a sequence of run-coded pairs, {N D}*.
  		N is a run-length * 4 + data code.
  		D, the data, depends on the data code...
  			0	skip N words, D is absent
  				(could be used to skip from one raster line to the next)
  			1	N words with all 4 bytes = D (1 byte)
  			2	N words all = D (4 bytes)
  			3	N words follow in D (4N bytes)
  		S and N are encoded as follows (see decodeIntFrom:)...
  			0-223	0-223
  			224-254	(0-30)*256 + next byte (0-7935)
  			255		next 4 bytes"	
  	"NOTE:  If fed with garbage, this routine could read past the end of ba, but it should fail before writing past the ned of bm."
  	| i code n anInt data end k pastEnd |
  	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin'>
+ 	<var: #bm declareC: 'int *bm'>
+ 	<var: #ba declareC: 'unsigned char *ba'>
- 	self var: #bm declareC: 'int *bm'.
- 	self var: #ba declareC: 'unsigned char *ba'.
  	i := index.  "byteArray read index"
  	end := ba size.
  	k := 1.  "bitmap write index"
  	pastEnd := bm size + 1.
  	[i <= end] whileTrue:
  		["Decode next run start N"
  		anInt := ba at: i.  i := i+1.
  		anInt <= 223 ifFalse:
  			[anInt <= 254
  				ifTrue: [anInt := (anInt-224)*256 + (ba at: i).  i := i+1]
  				ifFalse: [anInt := 0.
  						1 to: 4 do: [:j | anInt := (anInt bitShift: 8) + (ba at: i).  i := i+1]]].
  		n := anInt >> 2.
  		(k + n) > pastEnd ifTrue: [^ self primitiveFail].
  		code := anInt bitAnd: 3.
  		code = 0 ifTrue: ["skip"].
  		code = 1 ifTrue: ["n consecutive words of 4 bytes = the following byte"
  						data := ba at: i.  i := i+1.
  						data := data bitOr: (data bitShift: 8).
  						data := data bitOr: (data bitShift: 16).
  						1 to: n do: [:j | bm at: k put: data.  k := k+1]].
  		code = 2 ifTrue: ["n consecutive words = 4 following bytes"
  						data := 0.
  						1 to: 4 do: [:j | data := (data bitShift: 8) bitOr: (ba at: i).  i := i+1].
  						1 to: n do: [:j | bm at: k put: data.  k := k+1]].
  		code = 3 ifTrue: ["n consecutive words from the data..."
  						1 to: n do:
  							[:m | data := 0.
  							1 to: 4 do: [:j | data := (data bitShift: 8) bitOr: (ba at: i).  i := i+1].
  							bm at: k put: data.  k := k+1]]]!

Item was changed:
  ----- Method: Bitmap>>encodeBytesOf:in:at: (in category 'filing') -----
  encodeBytesOf: anInt in: ba at: i
  	"Copy the integer anInt into byteArray ba at index i, and return the next index"
  
+ 	<inline: true>
+ 	<var: #ba declareC: 'unsigned char *ba'>
- 	self inline: true.
- 	self var: #ba declareC: 'unsigned char *ba'.
  	0 to: 3 do:
  		[:j | ba at: i+j put: (anInt >> (3-j*8) bitAnd: 16rFF)].
  	^ i+4!

Item was changed:
  ----- Method: Bitmap>>encodeInt:in:at: (in category 'filing') -----
  encodeInt: anInt in: ba at: i
  	"Encode the integer anInt in byteArray ba at index i, and return the next index.
  	The encoding is as follows...
  		0-223	0-223
  		224-254	(0-30)*256 + next byte (0-7935)
  		255		next 4 bytes"		
  
+ 	<inline: true>
+ 	<var: #ba declareC: 'unsigned char *ba'>
- 	self inline: true.
- 	self var: #ba declareC: 'unsigned char *ba'.
  	anInt <= 223 ifTrue: [ba at: i put: anInt. ^ i+1].
  	anInt <= 7935 ifTrue: [ba at: i put: anInt//256+224. ba at: i+1 put: anInt\\256.  ^ i+2].
  	ba at: i put: 255.
  	^ self encodeBytesOf: anInt in: ba at: i+1!



More information about the Packages mailing list