[Vm-dev] Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich juan at jvuletich.org
Fri Oct 23 14:24:49 UTC 2009


Hi Folks,

David T. Lewis wrote:
>  
> On Thu, Oct 22, 2009 at 11:15:30AM -0300, Juan Vuletich wrote:
>   
>> I believe we need to add explicit declarations of all variables being 
>> unsigned. Or perhaps enhance a bit the code generator, by allowing a 
>> plugin to declare its default numeric type. For BitBlt it could be 
>> unsigned. For DSP stuff it could be float or double, making the Slang 
>> code much nicer by not needing all the explicit type declarations. What 
>> do you think?
>>     
>
> For most plugins, adding the explicit declarations for variables and
> method returns is sufficient, and takes care of the problem very well.
> For BitBlt it looks like it would be a lot of very tedious work. Does
> anyone have a code generator enhancement that would implement the
> default numeric type idea?
>
> The current default data type of sqInt is safe to use for object
> references for both 32 bit and 64 bit object memory. An implementation
> of default numeric types for plugins would need to be careful about
> method return declarations. If a method returns an object reference,
> it cannot be declared as int or long.
>
> If the goal is to fix issues in BitBlt, my guess is that the fastest
> way to get this done is to just grind through it and do all of the
> explicit type declarations for variables and method returns. It would
> take a few hours to do the work, but once it's done it's done.
>
> Dave

Ok. This is my first try at this. I went back to my old 6809 assembly 
language book to remember by 2's complement aritmethic. The bit pattern 
of the result of addition and substraction is not altered by considering 
a number signed or unsigned. The only operations that are affected are 
multiplication and comparisons. rgbMul works ok because it will never 
use the most significant bit (the sign bit). So I added the correct 
types only on those operations that needed to do correct comparisons. I 
also added the check for overflow in rgbAdd (the only place where it is 
needed).

I'm not sure if we should add the types everywhere, or it is ok to add 
them just to a few functions as I did. I'm running out of time today, 
anybody who can try to build a VM with this and test it, please do. (I 
didn't!)

There are a few more changes in the change-set. The change in rgbMul is 
to remove several repeated #bitAnd: . The rest of the changes were 
needed either to be able to generate the C code, or to run the simulator.

So, there are several issues that need more discussion here. Everybody, 
please check the code and comment on it.

Cheers,
Juan Vuletich
-------------- next part --------------
'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 23 October 2009 at 11:08:24 am'!

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:35'!
partitionedAdd: word1 to: word2 nBits: nBits nPartitions: nParts
	"Add word1 to word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors"
	| mask sum result maskedWord1 |
	self var: #word1 type: 'unsigned int'.
	self var: #word2 type: 'unsigned int'.
	self var: #mask type: 'unsigned int'.
	self var: #sum type: 'unsigned int'.
	self var: #result type: 'unsigned int'.
	self var: #maskedWord1 type: 'unsigned int'.
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		maskedWord1 := word1 bitAnd: mask.
		sum := maskedWord1 + (word2 bitAnd: mask).
		"result must not carry out of partition"
		(sum <= mask
				and: [ sum >= maskedWord1 ])
			ifTrue: [result := result bitOr: sum]
			ifFalse: [result := result bitOr: mask].
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:58'!
partitionedMax: word1 with: word2 nBits: nBits nPartitions: nParts
	"Max word1 to word2 as nParts partitions of nBits each"
	| mask result |
	self var: #word1 type: 'unsigned int'.
	self var: #word2 type: 'unsigned int'.
	self var: #mask type: 'unsigned int'.
	self var: #result type: 'unsigned int'.
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		result := result bitOr: ((word2 bitAnd: mask) max: (word1 bitAnd: mask)).
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 11:03'!
partitionedMin: word1 with: word2 nBits: nBits nPartitions: nParts
	"Min word1 to word2 as nParts partitions of nBits each"
	| mask result |
	self var: #word1 type: 'unsigned int'.
	self var: #word2 type: 'unsigned int'.
	self var: #mask type: 'unsigned int'.
	self var: #result type: 'unsigned int'.
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		result := result bitOr: ((word2 bitAnd: mask) min: (word1 bitAnd: mask)).
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 11:02'!
partitionedMul: word1 with: word2 nBits: nBits nPartitions: nParts
	"Multiply word1 with word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors.
	Bug in loop version when non-white background"

	| sMask product result dMask |
	sMask := maskTable at: nBits.  "partition mask starts at the right"
	dMask :=  sMask << nBits.
	result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 
				bitAnd: dMask) >> nBits.	"optimized first step"
	nParts = 1
		ifTrue: [ ^result ].
	product := (((word1>>nBits bitAnd: sMask)+1) * ((word2>>nBits bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product.
	nParts = 2
		ifTrue: [ ^result ].
	product := (((word1>>(2*nBits) bitAnd: sMask)+1) * ((word2>>(2*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product << nBits.
	nParts = 3
		ifTrue: [ ^result ].
	product := (((word1>>(3*nBits) bitAnd: sMask)+1) * ((word2>>(3*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product << (2*nBits).
	^ result

"	| sMask product result dMask |
	sMask := maskTable at: nBits.  'partition mask starts at the right'
	dMask :=  sMask << nBits.
	result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 
				bitAnd: dMask) >> nBits.	'optimized first step'
	nBits to: nBits * (nParts-1) by: nBits do: [:ofs |
		product := (((word1>>ofs bitAnd: sMask)+1) * ((word2>>ofs bitAnd: sMask)+1) - 1 bitAnd: dMask).
		result := result bitOr: (product bitAnd: dMask) << (ofs-nBits)].
	^ result"! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:57'!
partitionedSub: word1 from: word2 nBits: nBits nPartitions: nParts
	"Subtract word1 from word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors"
	| mask result p1 p2 |
	self var: #word1 type: 'unsigned int'.
	self var: #word2 type: 'unsigned int'.
	self var: #p1 type: 'unsigned int'.
	self var: #p2 type: 'unsigned int'.
	self var: #mask type: 'unsigned int'.
	self var: #result type: 'unsigned int'.
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		p1 := word1 bitAnd: mask.
		p2 := word2 bitAnd: mask.
		p1 < p2  "result is really abs value of thedifference"
			ifTrue: [result := result bitOr: p2 - p1]
			ifFalse: [result := result bitOr: p1 - p2].
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !


!BitBltSimulator methodsFor: 'simulation' stamp: 'jmv 10/23/2009 09:45'!
oopForPointer: pointer
	"This gets implemented by Macros in C, where its types will also be checked.
	oop is the width of a machine word, and pointer is a raw address."

	^ pointer! !


!CArrayAccessor methodsFor: 'accessing' stamp: 'jmv 10/23/2009 09:47'!
long32At: index
	| idx |
	idx := (offset + index) // 4 + 1.
	"Note: This is a special hack for BitBlt."
	(idx = (object basicSize + 1)) ifTrue:[^0].
	^object basicAt: idx! !

!CArrayAccessor methodsFor: 'accessing' stamp: 'jmv 10/23/2009 09:47'!
long32At: index put: value
	^object basicAt: (offset + index) // 4 + 1 put: value! !


!CCodeGenerator methodsFor: 'C code generator' stamp: 'jmv 10/23/2009 09:22'!
emitCConstantsOn: aStream 
	"Store the global variable declarations on the given stream."
	| unused constList node |
	unused := constants keys asSet.
	methods do:[:meth|
		meth parseTree nodesDo:[:n|
			n isConstant ifTrue:[unused remove: n name ifAbsent:[]]]].
	constList := constants keys reject:[:any| unused includes: any].
	aStream nextPutAll: '/*** Constants ***/';
		 cr.
	constList asSortedCollection do:[:varName|
		node := constants at: varName.
		node name isEmpty ifFalse:[
			aStream nextPutAll: '#define '.
			aStream nextPutAll: node name.
			aStream space.
			aStream nextPutAll: (self cLiteralFor: node value).
			aStream cr
		].
	].
	aStream cr.! !



More information about the Vm-dev mailing list