[Vm-dev] VM Maker: VMMaker.oscog-eem.3063.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Sep 7 21:06:23 UTC 2021


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.3063.mcz

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

Name: VMMaker.oscog-eem.3063
Author: eem
Time: 7 September 2021, 2:06:12.9568 pm
UUID: 91742da2-2b47-4a09-997c-b00f6642dbc3
Ancestors: VMMaker.oscog-eem.3062

BitBltPlugin:
faster checking for rule 41, avoiding unnecessary setting/testing prim fail flag, and function call when rule ~= 41.

faster simulation; the local implementation of BitBltSimulator>>long32At: is unnecessary.

(these are parenthetical as I try and work out why this is garbled in simulation:

| src | "just display O"
src := (UserInterfaceTheme current get: #standardFixedFont) formOf: $O.
Display fill: (0 at 32 extent: src extent) rule: Form over fillColor: Color white.
src displayOn: Display at: 0 at 32 rule: 34

=============== Diff against VMMaker.oscog-eem.3062 ===============

Item was changed:
  ----- Method: BitBltSimulation>>copyBitsFastPathSpecialised (in category 'setup') -----
  copyBitsFastPathSpecialised
  	"Perform the actual copyBits operation using the fast path specialised code; fail some cases by falling back to normal code.
  	Assume: Surfaces have been locked and clipping was performed."
  	<inline: false>
  
  	self
  		cppIf: #'ENABLE_FAST_BLT'
  		ifTrue:[
  	"set the affected area to 0 first"
  	affectedL := affectedR := affectedT := affectedB := 0.
  	
+ 	(combinationRule ~= 41 or: [self copyBitsRule41Test]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
- 	self copyBitsRule41Test.	
- 	(interpreterProxy failed not)
- 		ifFalse: [^ interpreterProxy primitiveFail].
  
   	"we skip the tryCopyingBitsQuickly and leave that to falback code"
  	 
  	(combinationRule = 30) | (combinationRule = 31) ifTrue:
  		["Check and fetch source alpha parameter for alpha blend"
  		interpreterProxy methodArgumentCount = 1
  			ifTrue: [sourceAlpha := interpreterProxy stackIntegerValue: 0.
  					(interpreterProxy failed not and: [(sourceAlpha >= 0) & (sourceAlpha <= 255)])
  						ifFalse: [^ interpreterProxy primitiveFail]]
  			ifFalse: [^ interpreterProxy primitiveFail]].
  
  	"we don't worry about bitCount"
  	"bitCount := 0."
  
  	"We don't  do - Choose and perform the actual copy loop."
  	"self performCopyLoop."
  
  	"this is done inversely to plain copyBitsLockedAndClipped"
  	(combinationRule ~= 22) & (combinationRule ~= 32) ifTrue:
  		["zero width and height; return the count"
  		affectedL := dx.
  		affectedR := dx + bbW.
  		affectedT := dy.
  		affectedB := dy + bbH].
  	
  	"Now we fill the 'operation' structure and pass it to the sneaky ARM code"
  	self cCode:'
  	// fill the operation structure
  	operation_t op;
  	op.combinationRule = combinationRule;
  	op.noSource = noSource;
  	op.src.bits = (void *) sourceBits;
  	op.src.pitch = sourcePitch;
  	op.src.depth = sourceDepth;
  	op.src.msb = sourceMSB;
  	op.src.x = sx;
  	op.src.y = sy;
  	op.dest.bits = (void *) destBits;
  	op.dest.pitch = destPitch;
  	op.dest.depth = destDepth;
  	op.dest.msb = destMSB;
  	op.dest.x = dx;
  	op.dest.y = dy;
  	op.width = bbW;
  	op.height = bbH;
  	op.cmFlags = cmFlags;
  	op.cmShiftTable = (void *) cmShiftTable;
  	op.cmMaskTable = (void *) cmMaskTable;
  	op.cmMask = cmMask;
  	op.cmLookupTable = (void *) cmLookupTable;
  	op.noHalftone = noHalftone;
  	op.halftoneHeight = halftoneHeight;
  	op.halftoneBase = (void *) halftoneBase;
  	if (combinationRule == 30 || combinationRule == 31) {
  		op.opt.sourceAlpha = sourceAlpha;
  	}
  	if (combinationRule == 41) {
  		op.opt.componentAlpha.componentAlphaModeColor = componentAlphaModeColor;
  		op.opt.componentAlpha.componentAlphaModeAlpha = componentAlphaModeAlpha;
  		op.opt.componentAlpha.gammaLookupTable = (void *) gammaLookupTable;
  		op.opt.componentAlpha.ungammaLookupTable = (void *) ungammaLookupTable;
  	}
  	// call the sneaky code
  	copyBitsDispatch(&op)'
  	]!

Item was changed:
  ----- Method: BitBltSimulation>>copyBitsLockedAndClipped (in category 'setup') -----
  copyBitsLockedAndClipped
  	"Perform the actual copyBits operation.
  	Assume: Surfaces have been locked and clipping was performed."
  	<inline: false>
  	
+ 	(combinationRule ~= 41 or: [self copyBitsRule41Test]) ifFalse:
- 	self copyBitsRule41Test.	
- 	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFail].
  
   	"Try a shortcut for stuff that should be run as quickly as possible"
  	self tryCopyingBitsQuickly ifTrue:
  		[^nil].
  
  	(combinationRule between: 30 and: 31) ifTrue:
  		["Check and fetch source alpha parameter for alpha blend"
  		 interpreterProxy methodArgumentCount = 1 ifFalse:
  			[^interpreterProxy primitiveFail].
  		 sourceAlpha := interpreterProxy stackIntegerValue: 0.
  		 (interpreterProxy failed
  		  or: [sourceAlpha < 0
  		  or: [sourceAlpha > 255]]) ifTrue:
  			[^interpreterProxy primitiveFail]].
  
  	bitCount := 0.
  	"Choose and perform the actual copy loop."
  	self performCopyLoop.
  
  	(combinationRule between: 30 and: 31)
  		ifTrue:"zero width and height; just return the count"
  			[affectedL := affectedR := affectedT := affectedB := 0]
  		ifFalse:
  			[hDir > 0
  				ifTrue: [affectedL := dx.
  						affectedR := dx + bbW]
  				ifFalse: [affectedL := dx - bbW + 1.
  						affectedR := dx + 1].
  			 vDir > 0
  				ifTrue: [affectedT := dy.
  						affectedB := dy + bbH]
  				ifFalse: [affectedT := dy - bbH + 1.
  						affectedB := dy + 1]]!

Item was changed:
  ----- Method: BitBltSimulation>>copyBitsRule41Test (in category 'setup') -----
  copyBitsRule41Test
+ 	"Test possible use of rule 41, rgbComponentAlpha:with: Set up some variables and answer if args were ok."
+ 	| numArgs gammaLookupTableOop ungammaLookupTableOop |
- 	"Test possible use of rule 41, rgbComponentAlpha:with: Nothing to return, just set up some variables"
- 	| gammaLookupTableOop ungammaLookupTableOop |
  	<inline: false>
  	
+ 	numArgs := interpreterProxy methodArgumentCount.
+ 	"fetch the forecolor into componentAlphaModeColor."
+ 	gammaLookupTable := nil.
+ 	ungammaLookupTable := nil.
+ 	numArgs >= 2 ifTrue:
+ 		[componentAlphaModeAlpha := interpreterProxy stackValue: numArgs - 2.
+ 		componentAlphaModeColor := interpreterProxy stackValue: numArgs - 1.
+ 		((interpreterProxy isIntegerObject: componentAlphaModeAlpha)
+ 		 and: [interpreterProxy isIntegerObject: componentAlphaModeColor]) ifFalse:
+ 			[^false].
+ 		componentAlphaModeAlpha := interpreterProxy integerValueOf: componentAlphaModeAlpha.
+ 		componentAlphaModeColor := interpreterProxy integerValueOf: componentAlphaModeColor.
+ 		numArgs = 4 ifTrue:
+ 			[gammaLookupTableOop := interpreterProxy stackValue: 1.
+ 			 (interpreterProxy isBytes: gammaLookupTableOop) ifTrue:
+ 				[gammaLookupTable := interpreterProxy firstIndexableField: gammaLookupTableOop].
+ 			 ungammaLookupTableOop := interpreterProxy stackValue: 0.
+ 			 (interpreterProxy isBytes: ungammaLookupTableOop) ifTrue:
+ 				[ungammaLookupTable := interpreterProxy firstIndexableField: ungammaLookupTableOop]].
+ 		^true].
+ 	componentAlphaModeAlpha := 255.
+ 	numArgs = 1 ifTrue:
+ 		[componentAlphaModeColor := interpreterProxy stackValue: 0.
+ 		 (interpreterProxy isIntegerObject: componentAlphaModeColor) ifFalse:
+ 			[^false].
+ 		componentAlphaModeColor := interpreterProxy integerValueOf: componentAlphaModeColor.
+ 		^true].
+ 	^false
- 	combinationRule = 41
- 		ifTrue:["fetch the forecolor into componentAlphaModeColor."
- 			componentAlphaModeAlpha := 255.
- 			componentAlphaModeColor := 16777215.
- 			gammaLookupTable := nil.
- 			ungammaLookupTable := nil.
- 			interpreterProxy methodArgumentCount >= 2
- 				ifTrue:[
- 					componentAlphaModeAlpha := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 2).
- 					(interpreterProxy failed not)
- 						ifFalse: [^ interpreterProxy primitiveFail].
- 					componentAlphaModeColor := interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 1).
- 					(interpreterProxy failed not)
- 						ifFalse: [^ interpreterProxy primitiveFail].
- 					interpreterProxy methodArgumentCount = 4
- 						ifTrue:[
- 							gammaLookupTableOop := interpreterProxy stackObjectValue: 1.
- 							(interpreterProxy isBytes: gammaLookupTableOop) 
- 								ifTrue:[gammaLookupTable := interpreterProxy firstIndexableField: gammaLookupTableOop.].
- 							ungammaLookupTableOop := interpreterProxy stackObjectValue: 0.
- 							(interpreterProxy isBytes: ungammaLookupTableOop) 
- 								ifTrue:[ungammaLookupTable := interpreterProxy firstIndexableField: ungammaLookupTableOop]]]
- 				ifFalse:[
- 					interpreterProxy methodArgumentCount = 1
- 						ifTrue: [
- 							componentAlphaModeColor := interpreterProxy stackIntegerValue: 0.
- 							(interpreterProxy failed not)
- 								ifFalse: [^ interpreterProxy primitiveFail]]
- 						ifFalse:[^ interpreterProxy primitiveFail]]].	
  
  
  !

Item was changed:
  ----- Method: BitBltSimulation>>dstLongAt: (in category 'memory access') -----
  dstLongAt: idx
  	<inline: #always>
  	self assert: idx asUnsignedInteger < endOfDestination.
+ 	^interpreterProxy long32At: idx!
- 	^self long32At: idx!

Item was changed:
  ----- Method: BitBltSimulation>>halftoneAt: (in category 'memory access') -----
  halftoneAt: idx
  	"Return a value from the halftone pattern."
  	<inline: #always>
+ 	^interpreterProxy long32At: halftoneBase + (idx \\ halftoneHeight * 4)!
- 	^self long32At: halftoneBase + (idx \\ halftoneHeight * 4)!

Item was changed:
  ----- Method: BitBltSimulation>>srcLongAt: (in category 'memory access') -----
  srcLongAt: idx
  	<inline: #always>
  	self assert: idx asUnsignedInteger < endOfSource.
+ 	^interpreterProxy long32At: idx!
- 	^self long32At: idx!

Item was changed:
  ----- Method: BitBltSimulation>>warpPickSmoothPixels:xDeltah:yDeltah:xDeltav:yDeltav:sourceMap:smoothing:dstShiftInc: (in category 'pixel mapping') -----
  warpPickSmoothPixels: nPixels
  	xDeltah: xDeltah yDeltah: yDeltah
  	xDeltav: xDeltav yDeltav: yDeltav
  	sourceMap: sourceMap
  	smoothing: n
  	dstShiftInc: dstShiftInc
  	"Pick n (sub-) pixels from the source form, mapped by sourceMap,
  	average the RGB values, map by colorMap and return the new word.
  	This version is only called from WarpBlt with smoothingCount > 1"
  	| rgb x y a r g b xx yy xdh ydh xdv ydv dstMask destWord i j k nPix |
  	<inline: false> "nope - too much stuff in here"
  	<var: #rgb type: #'unsigned int'>
  	dstMask := maskTable at: destDepth.
  	destWord := 0.
  	n = 2 "Try avoiding divides for most common n (divide by 2 is generated as shift)"
  		ifTrue:[xdh := xDeltah // 2. ydh := yDeltah // 2. 
  				xdv := xDeltav // 2. ydv := yDeltav // 2]
  		ifFalse:[xdh := xDeltah // n. ydh := yDeltah // n. 
  				xdv := xDeltav // n. ydv := yDeltav // n].
  	i := nPixels.
  	[
  		x := sx. y := sy.
  		a := r := g := b := 0.
  		"Pick and average n*n subpixels"
  		nPix := 0.  "actual number of pixels (not clipped and not transparent)"
  		j := n.
  		[
  			xx := x. yy := y.
  			k := n.
  			[
  				"get a single subpixel"
  				rgb := self pickWarpPixelAtX: xx y: yy.
  				(combinationRule=25 "PAINT" and: [rgb = 0]) ifFalse:[
  					"If not clipped and not transparent, then tally rgb values"
  					nPix := nPix + 1.
  					sourceDepth < 16 ifTrue:[
  						"Get RGBA values from sourcemap table"
+ 						rgb := interpreterProxy long32At: sourceMap + (rgb << 2).
- 						rgb := self long32At: sourceMap + (rgb << 2).
  					] ifFalse:["Already in RGB format"
  						sourceDepth = 16 
  								ifTrue:[rgb := self rgbMap16To32: rgb]
  								ifFalse:[rgb := self rgbMap32To32: rgb]].
  					b := b + (rgb bitAnd: 255).
  					g := g + (rgb >> 8 bitAnd: 255).
  					r := r + (rgb >> 16 bitAnd: 255).
  					a := a + (rgb >> 24)].
  				xx := xx + xdh.
  				yy := yy + ydh.
  			(k := k - 1) = 0] whileFalse.
  			x := x + xdv.
  			y := y + ydv.
  		(j := j - 1) = 0] whileFalse.
  
  		(nPix = 0 or: [combinationRule=25 "PAINT" and: [nPix < (n * n // 2)]]) ifTrue:[
  			rgb := 0  "All pixels were 0, or most were transparent"
  		] ifFalse:[
  			"normalize rgba sums"
  			nPix = 4 "Try to avoid divides for most common n"
  				ifTrue:[r := r >> 2.	g := g >> 2.	b := b >> 2.	a := a >> 2]
  				ifFalse:[	r := r // nPix.	g := g // nPix.	b := b // nPix.	a := a // nPix].
  			rgb := (a << 24) + (r << 16) + (g << 8) + b.
  
  			"map the pixel"
  			rgb = 0 ifTrue: [
  				"only generate zero if pixel is really transparent"
  				(r + g + b + a) > 0 ifTrue: [rgb := 1]].
  			rgb := self mapPixel: rgb flags: cmFlags.
  		].
  		"Mix it in"
  		destWord := destWord bitOr: (rgb bitAnd: dstMask) << dstBitShift.
  		dstBitShift := dstBitShift + dstShiftInc.
  		sx := sx + xDeltah.
  		sy := sy + yDeltah.
  	(i := i - 1) = 0] whileFalse.
  
  	^destWord
  !

Item was removed:
- ----- Method: BitBltSimulator>>long32At: (in category 'memory access') -----
- long32At: byteAddress
- 	^interpreterProxy long32At: byteAddress!



More information about the Vm-dev mailing list