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

Levente Uzonyi leves at caesar.elte.hu
Mon Feb 5 20:42:18 UTC 2018


On Mon, 5 Feb 2018, Tobias Pape wrote:

>
>> On 05.02.2018, at 21:23, Levente Uzonyi <leves at caesar.elte.hu> wrote:
>> 
>> On Mon, 5 Feb 2018, Tobias Pape wrote:
>> 
>>>> > On 05.02.2018, at 21:03, commits at source.squeak.org wrote:
>>>> Levente Uzonyi uploaded a new version of Graphics to project The Trunk:
>>>> http://source.squeak.org/trunk/Graphics-ul.392.mcz
>>>> ==================== Summary ====================
>>>> Name: Graphics-ul.392
>>>> Author: ul
>>>> Time: 22 January 2018, 12:28:13.814623 am
>>>> UUID: 8fbfdf92-ed6c-4460-b74b-fc649d42fe83
>>>> Ancestors: Graphics-tpr.391
>>>> - use ByteArray literals instead of Arrays
>>> 
>>> Is this any faster? Or do you have a different reasoning behind these changes?
>>> Just curious.
>> 
>> It helps the garbage collector do less work, because Arrays can point to any object, but ByteArrays can't, so ByteArrays don't have to be iterated over to find potential references, while Arrays do.
>> 
>
> Hmm. Does it really make such a big difference?

Of course 5 literals won't make any noticable difference, but you have to 
start somewhere. :)

Levente

>
> I'm unsure what we gain here, and fear that we lose clarity.
> People might think "use #[...] when using numbers" but get bitten when those numbers are >255, for example.
>
> Best regards
> 	-Tobias
>
>
>> Levente
>> 
>>> 
>>> Best regards
>>> 	-Tobias
>>> 
>>>> =============== Diff against Graphics-tpr.391 ===============
>>>> Item was changed:
>>>> ----- Method: BMPReadWriter>>nextPutImage: (in category 'writing') -----
>>>> nextPutImage: aForm
>>>> 	| bhSize rowBytes rgb data colorValues depth image ppw scanLineLen pixline |
>>>> 	depth := aForm depth.
>>>> + 	depth := #[1 4 8 32] detect: [ :each | each >= depth].
>>>> - 	depth := #(1 4 8 32 ) detect: [ :each | each >= depth].
>>>> 	image := aForm asFormOfDepth: depth.
>>>> 	image unhibernate.
>>>> 	bhSize := 14.  "# bytes in file header"
>>>> 	biSize := 40.  "info header size in bytes"
>>>> 	biWidth := image width.
>>>> 	biHeight := image height.
>>>> 	biClrUsed := depth = 32 ifTrue: [0] ifFalse:[1 << depth].  "No. color table entries"
>>>> 	bfOffBits := biSize + bhSize + (4*biClrUsed).
>>>> 	rowBytes := ((depth min: 24) * biWidth + 31 // 32) * 4.
>>>> 	biSizeImage := biHeight * rowBytes.
>>>>
>>>> 	"Write the file header"
>>>> 	stream position: 0.
>>>> 	stream nextLittleEndianNumber: 2 put: 19778.  "bfType = BM"
>>>> 	stream nextLittleEndianNumber: 4 put: bfOffBits + biSizeImage.  "Entire file size in bytes"
>>>> 	stream nextLittleEndianNumber: 4 put: 0.  "bfReserved"
>>>> 	stream nextLittleEndianNumber: 4 put: bfOffBits.  "Offset of bitmap data from start of hdr (and file)"
>>>>
>>>> 	"Write the bitmap info header"
>>>> 	stream position: bhSize.
>>>> 	stream nextLittleEndianNumber: 4 put: biSize.  "info header size in bytes"
>>>> 	stream nextLittleEndianNumber: 4 put: image width.  "biWidth"
>>>> 	stream nextLittleEndianNumber: 4 put: image height.  "biHeight"
>>>> 	stream nextLittleEndianNumber: 2 put: 1.  "biPlanes"
>>>> 	stream nextLittleEndianNumber: 2 put: (depth min: 24).  "biBitCount"
>>>> 	stream nextLittleEndianNumber: 4 put: 0.  "biCompression"
>>>> 	stream nextLittleEndianNumber: 4 put: biSizeImage.  "size of image section in bytes"
>>>> 	stream nextLittleEndianNumber: 4 put: 2800.  "biXPelsPerMeter"
>>>> 	stream nextLittleEndianNumber: 4 put: 2800.  "biYPelsPerMeter"
>>>> 	stream nextLittleEndianNumber: 4 put: biClrUsed.
>>>> 	stream nextLittleEndianNumber: 4 put: 0.  "biClrImportant"
>>>> 	biClrUsed > 0 ifTrue: [
>>>> 		"write color map; this works for ColorForms, too"
>>>> 		colorValues := image colormapIfNeededForDepth: 32.
>>>> 		1 to: biClrUsed do: [:i |
>>>> 			rgb := colorValues at: i.
>>>> 			0 to: 24 by: 8 do: [:j | stream nextPut: (rgb >> j bitAnd: 16rFF)]]].
>>>>
>>>> 	depth < 32 ifTrue: [
>>>> 		"depth = 1, 4 or 8."
>>>> 		data := image bits asByteArray.
>>>> 		ppw := 32 // depth.
>>>> 		scanLineLen := biWidth + ppw - 1 // ppw * 4.  "# of bytes in line"
>>>> 		1 to: biHeight do: [:i |
>>>> 			stream next: scanLineLen putAll: data startingAt: (biHeight-i)*scanLineLen+1.
>>>> 		].
>>>> 	] ifFalse: [
>>>> 		data := image bits.
>>>> 		pixline := ByteArray new: (((biWidth * 3 + 3) // 4) * 4).
>>>> 		1 to: biHeight do:[:i |
>>>> 			self store24BitBmpLine: pixline from: data startingAt: (biHeight-i)*biWidth+1 width: biWidth.
>>>> 			stream nextPutAll: pixline.
>>>> 		].
>>>> 	].
>>>> 	stream position = (bfOffBits + biSizeImage) ifFalse: [self error:'Write failure'].
>>>> 	stream close.!
>>>> Item was changed:
>>>> ----- Method: BitBlt class>>benchmark (in category 'benchmarks') -----
>>>> benchmark		"BitBlt benchmark"
>>>> 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
>>>> 	Attention: *this*may*take*a*while*"
>>>> 	| destRect log |
>>>> 	log := WriteStream on: String new.
>>>> 	destRect := 0 at 0 extent: 600 at 600.
>>>> 	"Form paint/Form over - the most common rules"
>>>> + 	#[25 3] do:[:rule|
>>>> - 	#( 25 3 ) do:[:rule|
>>>> 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
>>>> 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
>>>> + 		#[1 2 4 8 16 32] do:[:destDepth| | dest |
>>>> - 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
>>>> 			dest := nil.
>>>> 			dest := Form extent: destRect extent depth: destDepth.
>>>> 			Transcript cr.
>>>> 			log cr.
>>>> + 			#[1 2 4 8 16 32] do:[:sourceDepth| | t source bb |
>>>> - 			#(1 2 4 8 16 32) do:[:sourceDepth| | t source bb |
>>>> 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
>>>> 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
>>>> 				source := nil. bb := nil.
>>>> 				source := Form extent: destRect extent depth: sourceDepth.
>>>> 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
>>>> 				bb := WarpBlt toForm: dest.
>>>> 				bb sourceForm: source.
>>>> 				bb sourceRect: source boundingBox.
>>>> 				bb destRect: dest boundingBox.
>>>> 				bb colorMap: (source colormapIfNeededFor: dest).
>>>> 				bb combinationRule: rule.
>>>>
>>>> 				"Measure speed of copyBits"
>>>> 				t := Time millisecondsToRun:[bb copyBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				bb sourceForm: source destRect: source boundingBox.
>>>>
>>>> 				"Measure speed of 1x1 warpBits"
>>>> 				bb cellSize: 1.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 2x2 warpBits"
>>>> 				bb cellSize: 2.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 3x3 warpBits"
>>>> 				bb cellSize: 3.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>> 			].
>>>> 		].
>>>> 	].
>>>> 	^log contents!
>>>> Item was changed:
>>>> ----- Method: BitBlt class>>benchmark2 (in category 'benchmarks') -----
>>>> benchmark2		"BitBlt benchmark"
>>>> 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
>>>> 	Attention: *this*may*take*a*while*"
>>>> 	| destRect log |
>>>> 	log := WriteStream on: String new.
>>>> 	destRect := 0 at 0 extent: 600 at 600.
>>>> 	"Form paint/Form over - the most common rules"
>>>> + 	#[25 3] do:[:rule|
>>>> - 	#( 25 3 ) do:[:rule|
>>>> 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
>>>> 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
>>>> + 		#[1 2 4 8 16 32] do:[:destDepth| | dest |
>>>> - 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
>>>> 			dest := nil.
>>>> 			dest := Form extent: destRect extent depth: destDepth.
>>>> 			Transcript cr.
>>>> 			log cr.
>>>> + 			#[1 2 4 8 16 32] do:[:sourceDepth| | t bb source |
>>>> - 			#(1 2 4 8 16 32) do:[:sourceDepth| | t bb source |
>>>> 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
>>>> 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
>>>> 				source := nil. bb := nil.
>>>> 				source := Form extent: destRect extent depth: sourceDepth.
>>>> 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
>>>> 				bb := WarpBlt toForm: dest.
>>>> 				bb sourceForm: source.
>>>> 				bb sourceRect: source boundingBox.
>>>> 				bb destRect: dest boundingBox.
>>>> 				bb colorMap: (source colormapIfNeededFor: dest).
>>>> 				bb combinationRule: rule.
>>>>
>>>> 				"Measure speed of copyBits"
>>>> 				t := Time millisecondsToRun:[1 to: 10 do:[:i| bb copyBits]].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				bb sourceForm: source destRect: source boundingBox.
>>>>
>>>> 				"Measure speed of 1x1 warpBits"
>>>> 				bb cellSize: 1.
>>>> 				t := Time millisecondsToRun:[1 to: 4 do:[:i| bb warpBits]].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 2x2 warpBits"
>>>> 				bb cellSize: 2.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 3x3 warpBits"
>>>> 				bb cellSize: 3.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>> 			].
>>>> 		].
>>>> 	].
>>>> 	^log contents!
>>>> Item was changed:
>>>> ----- Method: BitBlt class>>benchmark3 (in category 'benchmarks') -----
>>>> benchmark3		"BitBlt benchmark"
>>>> 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
>>>> 	Attention: *this*may*take*a*while*"
>>>> 	| destRect log |
>>>> 	log := WriteStream on: String new.
>>>> 	destRect := 0 at 0 extent: 600 at 600.
>>>> 	"Form paint/Form over - the most common rules"
>>>> + 	#[25 3] do:[:rule|
>>>> - 	#( 25 3 ) do:[:rule|
>>>> 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
>>>> 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
>>>> + 		#[1 2 4 8 16 32] do:[:destDepth| | dest |
>>>> - 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
>>>> 			dest := nil.
>>>> 			dest := Form extent: destRect extent depth: destDepth.
>>>> 			Transcript cr.
>>>> 			log cr.
>>>> + 			#[1 2 4 8 16 32] do:[:sourceDepth| | t source bb |
>>>> - 			#(1 2 4 8 16 32) do:[:sourceDepth| | t source bb |
>>>> 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
>>>> 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
>>>> 				source := nil. bb := nil.
>>>> 				source := Form extent: destRect extent depth: sourceDepth.
>>>> 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
>>>> 				bb := WarpBlt toForm: dest.
>>>> 				bb sourceForm: source.
>>>> 				bb sourceRect: source boundingBox.
>>>> 				bb destRect: dest boundingBox.
>>>> 				bb colorMap: (source colormapIfNeededFor: dest).
>>>> 				bb combinationRule: rule.
>>>>
>>>> 				"Measure speed of copyBits"
>>>> 				t := Time millisecondsToRun:[1 to: 10 do:[:i| bb copyBits]].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				bb sourceForm: source destRect: source boundingBox.
>>>>
>>>> 				"Measure speed of 1x1 warpBits"
>>>> 				bb cellSize: 1.
>>>> 				t := Time millisecondsToRun:[1 to: 4 do:[:i| bb warpBits]].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 2x2 warpBits"
>>>> 				bb cellSize: 2.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>>
>>>> 				"Measure speed of 3x3 warpBits"
>>>> 				bb cellSize: 3.
>>>> 				t := Time millisecondsToRun:[bb warpBits].
>>>> 				Transcript tab; show: t printString.
>>>> 				log tab; nextPutAll: t printString.
>>>> 			].
>>>> 		].
>>>> 	].
>>>> 	^log contents!
>>>> Item was changed:
>>>> ----- Method: GIFReadWriter>>writeHeader (in category 'private-encoding') -----
>>>> writeHeader
>>>>
>>>> 	| byte |
>>>> 	stream position = 0 ifTrue: [
>>>> 		"For first image only"
>>>> 		self nextPutAll: 'GIF89a' asByteArray.
>>>> 		self writeWord: width.	"Screen Width"
>>>> 		self writeWord: height.	"Screen Height"
>>>> 		byte := 16r80.  "has color map"
>>>> 		byte := byte bitOr: ((bitsPerPixel - 1) bitShift: 5).  "color resolution"
>>>> 		byte := byte bitOr: bitsPerPixel - 1.  "bits per pixel"
>>>> 		self nextPut: byte.
>>>> 		self nextPut: 0.		"background color."
>>>> 		self nextPut: 0.		"reserved"
>>>> 		colorPalette do: [:pixelValue |
>>>> 			self	nextPut: ((pixelValue bitShift: -16) bitAnd: 255);
>>>> 				nextPut: ((pixelValue bitShift: -8) bitAnd: 255);
>>>> 				nextPut: (pixelValue bitAnd: 255)].
>>>> 		loopCount notNil ifTrue: [
>>>> 			"Write a Netscape loop chunk"
>>>> 			self nextPut: Extension.
>>>> + 			self nextPutAll: #[255 11 78 69 84 83 67 65 80 69 50 46 48 3 1].
>>>> - 			self nextPutAll: #(255 11 78 69 84 83 67 65 80 69 50 46 48 3 1) asByteArray.
>>>> 			self writeWord: loopCount.
>>>> 			self nextPut: 0]].
>>>>
>>>> 	delay notNil | transparentIndex notNil ifTrue: [
>>>> 		self nextPut: Extension;
>>>> 			nextPutAll: #(16rF9 4) asByteArray;
>>>> 			nextPut: (transparentIndex isNil ifTrue: [0] ifFalse: [9]);
>>>> 			writeWord: (delay isNil ifTrue: [0] ifFalse: [delay]);
>>>> 			nextPut: (transparentIndex isNil ifTrue: [0] ifFalse: [transparentIndex]);
>>>> 			nextPut: 0].
>>>>
>>>> 	self nextPut: ImageSeparator.
>>>> 	self writeWord: 0.		"Image Left"
>>>> 	self writeWord: 0.		"Image Top"
>>>> 	self writeWord: width.	"Image Width"
>>>> 	self writeWord: height.	"Image Height"
>>>> 	byte := interlace ifTrue: [16r40] ifFalse: [0].
>>>> 	self nextPut: byte.
>>>> !
>>>> 
>>


More information about the Squeak-dev mailing list