[Vm-dev] [commit] r2226 - OSCog source as per VMMaker-oscog.18. JMV's fixes for RGBA combination rules in

commits at squeakvm.org commits at squeakvm.org
Sun Jul 4 02:33:33 UTC 2010


Author: eliot
Date: 2010-07-03 19:33:33 -0700 (Sat, 03 Jul 2010)
New Revision: 2226

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/macbuild/CroquetPlugin/
   branches/Cog/macbuild/FloatArrayPlugin/
   branches/Cog/macbuild/mpeg3Plugin/
   branches/Cog/src/plugins/BitBltPlugin/BitBltPlugin.c
Log:
OSCog source as per VMMaker-oscog.18.  JMV's fixes for RGBA combination rules in
BitBlt.  Some additional svn:ignore state for the build dirs.


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes	2010-06-27 17:29:27 UTC (rev 2225)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes	2010-07-04 02:33:33 UTC (rev 2226)
@@ -117090,4 +117090,360 @@
 		platformDir: (FileDirectory default / '../platforms') fullName
 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
 
-----QUIT----{26 June 2010 . 4:22:16 pm} VMMaker-Squeak4.1.image priorSource: 4750018!
\ No newline at end of file
+----QUIT----{26 June 2010 . 4:22:16 pm} VMMaker-Squeak4.1.image priorSource: 4750018!
+
+----STARTUP----{3 July 2010 . 12:19:07 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{3 July 2010 . 5:26:37 pm} VMMaker-Squeak4.1.image priorSource: 4755495!
+
+----STARTUP----{3 July 2010 . 7:09:07 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/26/2009 08:58' prior: 34007783!
+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 |
+	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)"
+	<var: #word1 type: 'unsigned int'>
+	<var: #word2 type: 'unsigned int'>
+	<var: #mask type: 'unsigned int'>
+	<var: #sum type: 'unsigned int'>
+	<var: #result type: 'unsigned int'>
+	<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).
+		(sum <= mask "result must not carry out of partition"
+				and: [ sum >= maskedWord1 ])	"This is needed because in C, integer arithmetic overflows silently!! (jmv)"
+			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/26/2009 08:59' prior: 34008434!
+partitionedMax: word1 with: word2 nBits: nBits nPartitions: nParts
+	"Max word1 to word2 as nParts partitions of nBits each"
+	| mask result |
+	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)"
+	<var: #word1 type: 'unsigned int'>
+	<var: #word2 type: 'unsigned int'>
+	<var: #mask type: 'unsigned int'>
+	<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/26/2009 08:59' prior: 34008911!
+partitionedMin: word1 with: word2 nBits: nBits nPartitions: nParts
+	"Min word1 to word2 as nParts partitions of nBits each"
+	| mask result |
+	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)"
+	<var: #word1 type: 'unsigned int'>
+	<var: #word2 type: 'unsigned int'>
+	<var: #mask type: 'unsigned int'>
+	<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/26/2009 09:01' prior: 34009387!
+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 |
+	"In C, integer multiplication might answer a wrong value if the unsigned values are declared as signed.
+	This problem does not affect this method, because the most significant bit (i.e. the sign bit) will
+	always be zero (jmv)"
+	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/26/2009 08:59' prior: 34010765!
+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 |
+	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)"
+	<var: #word1 type: 'unsigned int'>
+	<var: #word2 type: 'unsigned int'>
+	<var: #p1 type: 'unsigned int'>
+	<var: #p2 type: 'unsigned int'>
+	<var: #mask type: 'unsigned int'>
+	<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
+! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34015802!
+rgbAdd: sourceWord with: destinationWord
+	<inline: false>
+	destDepth < 16 ifTrue:
+		["Add each pixel separately"
+		^ self partitionedAdd: sourceWord to: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Add RGB components of each pixel separately"
+		^ (self partitionedAdd: sourceWord to: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedAdd: sourceWord>>16 to: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Add RGBA components of the pixel separately"
+		^ self partitionedAdd: sourceWord to: destinationWord
+						nBits: 8 nPartitions: 4]! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34018041!
+rgbMax: sourceWord with: destinationWord
+	<inline: false>
+	destDepth < 16 ifTrue:
+		["Max each pixel separately"
+		^ self partitionedMax: sourceWord with: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Max RGB components of each pixel separately"
+		^ (self partitionedMax: sourceWord with: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedMax: sourceWord>>16 with: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Max RGBA components of the pixel separately"
+		^ self partitionedMax: sourceWord with: destinationWord
+						nBits: 8 nPartitions: 4]! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34019517!
+rgbMinInvert: wordToInvert with: destinationWord
+	| sourceWord |
+	<inline: false>
+	sourceWord := wordToInvert bitInvert32.
+	destDepth < 16 ifTrue:
+		["Min each pixel separately"
+		^ self partitionedMin: sourceWord with: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Min RGB components of each pixel separately"
+		^ (self partitionedMin: sourceWord with: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedMin: sourceWord>>16 with: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Min RGBA components of the pixel separately"
+		^ self partitionedMin: sourceWord with: destinationWord
+						nBits: 8 nPartitions: 4]! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34018779!
+rgbMin: sourceWord with: destinationWord
+	<inline: false>
+	destDepth < 16 ifTrue:
+		["Min each pixel separately"
+		^ self partitionedMin: sourceWord with: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Min RGB components of each pixel separately"
+		^ (self partitionedMin: sourceWord with: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedMin: sourceWord>>16 with: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Min RGBA components of the pixel separately"
+		^ self partitionedMin: sourceWord with: destinationWord
+						nBits: 8 nPartitions: 4]! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34020320!
+rgbMul: sourceWord with: destinationWord
+	<inline: false>
+	destDepth < 16 ifTrue:
+		["Mul each pixel separately"
+		^ self partitionedMul: sourceWord with: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Mul RGB components of each pixel separately"
+		^ (self partitionedMul: sourceWord with: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedMul: sourceWord>>16 with: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Mul RGBA components of the pixel separately"
+		^ self partitionedMul: sourceWord with: destinationWord
+						nBits: 8 nPartitions: 4]
+
+"	| scanner |
+	Display repaintMorphicDisplay.
+	scanner := DisplayScanner quickPrintOn: Display.
+	MessageTally time: [0 to: 760 by: 4 do:  [:y |scanner drawString: 'qwrepoiuasfd=)(/&()=#!!lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,Mqwrepoiuasfd=)(/&()=#!!lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,M1234124356785678' at: 0 at y]]. "! !
+!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 4/1/2009 08:39' prior: 34021394!
+rgbSub: sourceWord with: destinationWord
+	<inline: false>
+	destDepth < 16 ifTrue:
+		["Sub each pixel separately"
+		^ self partitionedSub: sourceWord from: destinationWord
+						nBits: destDepth nPartitions: destPPW].
+	destDepth = 16 ifTrue:
+		["Sub RGB components of each pixel separately"
+		^ (self partitionedSub: sourceWord from: destinationWord
+						nBits: 5 nPartitions: 3)
+		+ ((self partitionedSub: sourceWord>>16 from: destinationWord>>16
+						nBits: 5 nPartitions: 3) << 16)]
+	ifFalse:
+		["Sub RGBA components of the pixel separately"
+		^ self partitionedSub: sourceWord from: destinationWord
+						nBits: 8 nPartitions: 4]! !
+!CogMethodSurrogate methodsFor: 'comparing' stamp: 'eem 7/1/2010 12:53'!
+isZero
+	^address = 0! !
+!CogVMSimulator methodsFor: 'testing' stamp: 'eem 6/29/2010 14:38' prior: 34903416!
+run
+	"Just run"
+	quitBlock := [([transcript dependents anyOne outermostMorphThat: [:m| m isSystemWindow]]
+					on: Error
+					do: [:ex| nil])
+						ifNotNil: [:window| (UIManager default confirm: 'close?') ifTrue: [window delete]].
+				  ^self].
+	self initStackPages.
+	self loadInitialContext.
+	self initialEnterSmalltalkExecutive! !
+!CogVMSimulator methodsFor: 'testing' stamp: 'eem 6/29/2010 14:38' prior: 34903612!
+runWithBreakCount: theBreakCount
+	"Just run, halting when byteCount is reached"
+	quitBlock := [([transcript dependents anyOne outermostMorphThat: [:m| m isSystemWindow]]
+					on: Error
+					do: [:ex| nil])
+						ifNotNil: [:window| (UIManager default confirm: 'close?') ifTrue: [window delete]].
+				  ^self].
+	breakCount := theBreakCount.
+	self initStackPages.
+	self loadInitialContext.
+	self initialEnterSmalltalkExecutive! !
+!CogVMSimulator methodsFor: 'debug printing' stamp: 'eem 7/1/2010 19:39' prior: 38176688!
+symbolicMethod: aMethod
+	| pc end latestContinuation |
+	pc := latestContinuation := self startPCOfMethod: aMethod.
+	end := self byteSizeOf: aMethod.
+	[pc <= end] whileTrue:
+		[| byte byte2 byte3 byte4 type offset jumpTarget |
+		 byte := self fetchByte: pc ofObject: aMethod.
+		 type := byte // 16.
+		 offset := byte \\ 16.  
+		 (type =7 and: [offset >= 8 and: [pc >= latestContinuation]]) ifTrue:"Return bytecodes (possible lastPC here)"
+			[end := pc].
+		 (type = 8 and: [offset = 15]) ifTrue: "closure creation; update latest continuation"
+			[byte3 := self fetchByte: pc + 2 ofObject: aMethod.
+			 byte4 := self fetchByte: pc + 3 ofObject: aMethod.
+			 jumpTarget := (byte3 * 256) + byte4 + pc + 4.
+			 jumpTarget > latestContinuation ifTrue: [latestContinuation := jumpTarget]].
+		 type=9 ifTrue: "Short jumps (need to update latest continuation"
+			[jumpTarget := (offset < 8 ifTrue: [offset] ifFalse: [offset - 8]) + pc + 2.
+			jumpTarget > latestContinuation ifTrue: [latestContinuation := jumpTarget]].
+		 type=10 ifTrue: "Long jumps (need to update latest continuation)"
+			[byte2 := self fetchByte: pc + 1 ofObject: aMethod.
+			 jumpTarget := (offset < 8 ifTrue: [offset - 4] ifFalse: [offset bitAnd: 3]) * 256 + byte2 + pc + 2.
+			 jumpTarget > latestContinuation ifTrue: [latestContinuation := jumpTarget]].
+
+		 transcript print: pc + 1 ; space.
+		 byte printOn: transcript base: 16 length: 2 padded: false.
+		 transcript space; nextPutAll: (self symbolic: byte at: pc inMethod: aMethod); cr; flush.
+		 pc := type = 8 "extensions"
+					ifTrue: [pc + (#(2 2 2 2 3 2 2 1 1 1 2 1 3 3 3 4) at: byte \\ 16 + 1)]
+					ifFalse: [type = 10 "long jumps"
+								ifTrue: [pc + 2]
+								ifFalse: [pc + 1]]]! !
+!StackInterpreterSimulator methodsFor: 'testing' stamp: 'eem 6/29/2010 14:38' prior: 38305986!
+run
+	"Just run"
+	quitBlock := [([transcript dependents anyOne outermostMorphThat: [:m| m isSystemWindow]]
+					on: Error
+					do: [:ex| nil])
+						ifNotNil: [:window| (UIManager default confirm: 'close?') ifTrue: [window delete]].
+				  ^self].
+	self initStackPages.
+	self loadInitialContext.
+	self internalizeIPandSP.
+	self fetchNextBytecode.
+	[true] whileTrue:
+		[self assertValidExecutionPointers.
+		 atEachStepBlock value. "N.B. may be nil"
+		 self dispatchOn: currentBytecode in: BytecodeTable.
+		 self incrementByteCount].
+	localIP := localIP - 1.
+	"undo the pre-increment of IP before returning"
+	self externalizeIPandSP! !
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+	rep user: user;
+	password: pw ]!
+
+"VMMaker"!
+
+VMMaker
+		generate: StackInterpreter
+		to: (FileDirectory default / '../stacksrc') fullName
+		platformDir: (FileDirectory default / '../platforms') fullName
+		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
+
+VMMaker
+		generate: CoInterpreter
+		to: (FileDirectory default / '../src') fullName
+		platformDir: (FileDirectory default / '../platforms') fullName
+		excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin)!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+	rep user: user;
+	password: pw ]!
+
+----QUIT----{3 July 2010 . 7:22:26 pm} VMMaker-Squeak4.1.image priorSource: 4755495!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)


Property changes on: branches/Cog/macbuild/CroquetPlugin
___________________________________________________________________
Added: svn:ignore
   + build



Property changes on: branches/Cog/macbuild/FloatArrayPlugin
___________________________________________________________________
Added: svn:ignore
   + build



Property changes on: branches/Cog/macbuild/mpeg3Plugin
___________________________________________________________________
Added: svn:ignore
   + build


Modified: branches/Cog/src/plugins/BitBltPlugin/BitBltPlugin.c
===================================================================
--- branches/Cog/src/plugins/BitBltPlugin/BitBltPlugin.c	2010-06-27 17:29:27 UTC (rev 2225)
+++ branches/Cog/src/plugins/BitBltPlugin/BitBltPlugin.c	2010-07-04 02:33:33 UTC (rev 2226)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	VMPluginCodeGenerator VMMaker-oscog.12 uuid: a34fa6af-c3a0-453e-8450-8525342057ac
+	VMPluginCodeGenerator VMMaker-oscog.18 uuid: 66fabf9e-52f4-43aa-a0fc-023e1c0e686e
    from
-	BitBltSimulation VMMaker-oscog.12 uuid: a34fa6af-c3a0-453e-8450-8525342057ac
+	BitBltSimulation VMMaker-oscog.18 uuid: 66fabf9e-52f4-43aa-a0fc-023e1c0e686e
  */
-static char __buildInfo[] = "BitBltSimulation VMMaker-oscog.12 uuid: a34fa6af-c3a0-453e-8450-8525342057ac " __DATE__ ;
+static char __buildInfo[] = "BitBltSimulation VMMaker-oscog.18 uuid: 66fabf9e-52f4-43aa-a0fc-023e1c0e686e " __DATE__ ;
 
 
 
@@ -146,12 +146,12 @@
 static sqInt msg(char *s);
 static sqInt OLDrgbDiffwith(sqInt sourceWord, sqInt destinationWord);
 static sqInt OLDtallyIntoMapwith(sqInt sourceWord, sqInt destinationWord);
-static sqInt partitionedAddtonBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
+static sqInt partitionedAddtonBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts);
 static sqInt partitionedANDtonBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
-static sqInt partitionedMaxwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
-static sqInt partitionedMinwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
+static sqInt partitionedMaxwithnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts);
+static sqInt partitionedMinwithnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts);
 static sqInt partitionedMulwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
-static sqInt partitionedSubfromnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts);
+static sqInt partitionedSubfromnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts);
 static sqInt performCopyLoop(void);
 static sqInt pickSourcePixelsflagssrcMaskdestMasksrcShiftIncdstShiftInc(sqInt nPixels, sqInt mapperFlags, sqInt srcMask, sqInt dstMask, sqInt srcShiftInc, sqInt dstShiftInc);
 static sqInt pickWarpPixelAtXy(sqInt xx, sqInt yy);
@@ -266,9 +266,9 @@
 };
 static const char *moduleName =
 #ifdef SQUEAK_BUILTIN_PLUGIN
-	"BitBltPlugin VMMaker-oscog.12 (i)"
+	"BitBltPlugin VMMaker-oscog.18 (i)"
 #else
-	"BitBltPlugin VMMaker-oscog.12 (e)"
+	"BitBltPlugin VMMaker-oscog.18 (e)"
 #endif
 ;
 static sqInt noHalftone;
@@ -3795,13 +3795,20 @@
 
 /*	Add word1 to word2 as nParts partitions of nBits each.
 	This is useful for packed pixels, or packed colors */
+/*	In C, most arithmetic operations answer the same bit pattern regardless of
+	the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However,
+	comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)
+ */
 
 static sqInt
-partitionedAddtonBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts) {
+partitionedAddtonBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts) {
     sqInt i;
-    sqInt mask;
-    sqInt result;
-    sqInt sum;
+    unsigned int mask;
+    unsigned int maskedWord1;
+    unsigned int result;
+    unsigned int sum;
 
 
 	/* partition mask starts at the right */
@@ -3809,10 +3816,12 @@
 	mask = maskTable[nBits];
 	result = 0;
 	for (i = 1; i <= nParts; i += 1) {
-		sum = (word1 & mask) + (word2 & mask);
-		if (sum <= mask) {
+		maskedWord1 = word1 & mask;
+		sum = maskedWord1 + (word2 & mask);
+		if ((sum <= mask)
+		 && (sum >= maskedWord1)) {
 
-			/* result must not carry out of partition */
+			/* This is needed because in C, integer arithmetic overflows silently! (jmv) */
 
 			result = result | sum;
 		}
@@ -3857,12 +3866,18 @@
 
 
 /*	Max word1 to word2 as nParts partitions of nBits each */
+/*	In C, most arithmetic operations answer the same bit pattern regardless of
+	the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However,
+	comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)
+ */
 
 static sqInt
-partitionedMaxwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts) {
+partitionedMaxwithnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts) {
     sqInt i;
-    sqInt mask;
-    sqInt result;
+    unsigned int mask;
+    unsigned int result;
 
 
 	/* partition mask starts at the right */
@@ -3881,12 +3896,18 @@
 
 
 /*	Min word1 to word2 as nParts partitions of nBits each */
+/*	In C, most arithmetic operations answer the same bit pattern regardless of
+	the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However,
+	comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)
+ */
 
 static sqInt
-partitionedMinwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts) {
+partitionedMinwithnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts) {
     sqInt i;
-    sqInt mask;
-    sqInt result;
+    unsigned int mask;
+    unsigned int result;
 
 
 	/* partition mask starts at the right */
@@ -3907,6 +3928,12 @@
 /*	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 */
+/*	In C, integer multiplication might answer a wrong value if the unsigned
+	values are declared as signed.
+	This problem does not affect this method, because the most significant bit
+	(i.e. the sign bit) will
+	always be zero (jmv)
+ */
 
 static sqInt
 partitionedMulwithnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts) {
@@ -3924,24 +3951,41 @@
 	/* optimized first step */
 
 	result = ((usqInt) (((((word1 & sMask) + 1) * ((word2 & sMask) + 1)) - 1) & dMask)) >> nBits;
+	if (nParts == 1) {
+		return result;
+	}
 	product = (((((((usqInt) word1) >> nBits) & sMask) + 1) * (((((usqInt) word2) >> nBits) & sMask) + 1)) - 1) & dMask;
-	result = result | (product & dMask);
+	result = result | product;
+	if (nParts == 2) {
+		return result;
+	}
 	product = (((((((usqInt) word1) >> (2 * nBits)) & sMask) + 1) * (((((usqInt) word2) >> (2 * nBits)) & sMask) + 1)) - 1) & dMask;
-	result = result | ((product & dMask) << nBits);
+	result = result | (product << nBits);
+	if (nParts == 3) {
+		return result;
+	}
+	product = (((((((usqInt) word1) >> (3 * nBits)) & sMask) + 1) * (((((usqInt) word2) >> (3 * nBits)) & sMask) + 1)) - 1) & dMask;
+	result = result | (product << (2 * nBits));
 	return result;
 }
 
 
 /*	Subtract word1 from word2 as nParts partitions of nBits each.
 	This is useful for packed pixels, or packed colors */
+/*	In C, most arithmetic operations answer the same bit pattern regardless of
+	the operands being signed or unsigned ints
+	(this is due to the way 2's complement numbers work). However,
+	comparisions might fail. Add the proper declaration of
+	words as unsigned int in those cases where comparisions are done (jmv)
+ */
 
 static sqInt
-partitionedSubfromnBitsnPartitions(sqInt word1, sqInt word2, sqInt nBits, sqInt nParts) {
+partitionedSubfromnBitsnPartitions(unsigned int word1, unsigned int word2, sqInt nBits, sqInt nParts) {
     sqInt i;
-    sqInt mask;
-    sqInt p1;
-    sqInt p2;
-    sqInt result;
+    unsigned int mask;
+    unsigned int p1;
+    unsigned int p2;
+    unsigned int result;
 
 
 	/* partition mask starts at the right */
@@ -4854,7 +4898,7 @@
 		return (partitionedAddtonBitsnPartitions(sourceWord, destinationWord, 5, 3)) + ((partitionedAddtonBitsnPartitions(((usqInt) sourceWord) >> 16, ((usqInt) destinationWord) >> 16, 5, 3)) << 16);
 	}
 	else {
-		return partitionedAddtonBitsnPartitions(sourceWord, destinationWord, 8, 3);
+		return partitionedAddtonBitsnPartitions(sourceWord, destinationWord, 8, 4);
 	}
 }
 
@@ -5007,10 +5051,10 @@
 rgbMaxwith(sqInt sourceWord, sqInt destinationWord) {
     sqInt i;
     sqInt i1;
-    sqInt mask;
-    sqInt mask3;
-    sqInt result;
-    sqInt result1;
+    unsigned int mask;
+    unsigned int mask3;
+    unsigned int result;
+    unsigned int result1;
 
 	if (destDepth < 16) {
 		/* begin partitionedMax:with:nBits:nPartitions: */
@@ -5038,7 +5082,7 @@
 
 		mask3 = maskTable[8];
 		result1 = 0;
-		for (i1 = 1; i1 <= 3; i1 += 1) {
+		for (i1 = 1; i1 <= 4; i1 += 1) {
 			result1 = result1 | ((((destinationWord & mask3) < (sourceWord & mask3)) ? (sourceWord & mask3) : (destinationWord & mask3)));
 
 			/* slide left to next partition */
@@ -5053,10 +5097,10 @@
 rgbMinInvertwith(sqInt wordToInvert, sqInt destinationWord) {
     sqInt i;
     sqInt i1;
-    sqInt mask;
-    sqInt mask3;
-    sqInt result;
-    sqInt result1;
+    unsigned int mask;
+    unsigned int mask3;
+    unsigned int result;
+    unsigned int result1;
     sqInt sourceWord;
 
 	sourceWord = ~wordToInvert;
@@ -5086,7 +5130,7 @@
 
 		mask3 = maskTable[8];
 		result1 = 0;
-		for (i1 = 1; i1 <= 3; i1 += 1) {
+		for (i1 = 1; i1 <= 4; i1 += 1) {
 			result1 = result1 | ((((destinationWord & mask3) < (sourceWord & mask3)) ? (destinationWord & mask3) : (sourceWord & mask3)));
 
 			/* slide left to next partition */
@@ -5101,10 +5145,10 @@
 rgbMinwith(sqInt sourceWord, sqInt destinationWord) {
     sqInt i;
     sqInt i1;
-    sqInt mask;
-    sqInt mask3;
-    sqInt result;
-    sqInt result1;
+    unsigned int mask;
+    unsigned int mask3;
+    unsigned int result;
+    unsigned int result1;
 
 	if (destDepth < 16) {
 		/* begin partitionedMin:with:nBits:nPartitions: */
@@ -5132,7 +5176,7 @@
 
 		mask3 = maskTable[8];
 		result1 = 0;
-		for (i1 = 1; i1 <= 3; i1 += 1) {
+		for (i1 = 1; i1 <= 4; i1 += 1) {
 			result1 = result1 | ((((destinationWord & mask3) < (sourceWord & mask3)) ? (destinationWord & mask3) : (sourceWord & mask3)));
 
 			/* slide left to next partition */
@@ -5152,7 +5196,7 @@
 		return (partitionedMulwithnBitsnPartitions(sourceWord, destinationWord, 5, 3)) + ((partitionedMulwithnBitsnPartitions(((usqInt) sourceWord) >> 16, ((usqInt) destinationWord) >> 16, 5, 3)) << 16);
 	}
 	else {
-		return partitionedMulwithnBitsnPartitions(sourceWord, destinationWord, 8, 3);
+		return partitionedMulwithnBitsnPartitions(sourceWord, destinationWord, 8, 4);
 	}
 }
 
@@ -5165,7 +5209,7 @@
 		return (partitionedSubfromnBitsnPartitions(sourceWord, destinationWord, 5, 3)) + ((partitionedSubfromnBitsnPartitions(((usqInt) sourceWord) >> 16, ((usqInt) destinationWord) >> 16, 5, 3)) << 16);
 	}
 	else {
-		return partitionedSubfromnBitsnPartitions(sourceWord, destinationWord, 8, 3);
+		return partitionedSubfromnBitsnPartitions(sourceWord, destinationWord, 8, 4);
 	}
 }
 



More information about the Vm-dev mailing list