[Vm-dev] VM Maker: VMMaker.oscog-nice.1736.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Mar 19 14:44:07 UTC 2016


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1736.mcz

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

Name: VMMaker.oscog-nice.1736
Author: nice
Time: 19 March 2016, 3:41:39.741 pm
UUID: 193c2046-4773-44ea-9455-a138be7b0992
Ancestors: VMMaker.oscog-nice.1735

Fix another bug of 1732.nice commit which broke primitiveBitAnd and primitiveBitOr

The symptom is this one at least in stack spur 64bits:
(-1 bitAnd: -1) -> -1 "correct"
(-1 perform: 1bitAnd: with: -1) -> 16r1FFFFFFF 'huh?"

it's -1 asUnsignedInteger >> 3...

The first one is working Ok because it's using bytecodePrimBitAnd which is very simple and correct.

here is the mistake I introduced a #usqInt type hint in slang.
At the time I did it, it was to reduce the number of signed mismatch warnings which are a plague. Yes but:

integerArgument := self positiveMachineIntegerValueOf: integerArgument.

Ouch, the return value is supposed to be unsigned.
While the parameter has to be signed in order to have the isIntegerObject: bit tricks working once inlined by slang...
So reusing the variable name for two different things was not a good idea finally (it rarely is).

This doesn't happen in my own branch because I've carefully rewritten the shift logic to use exclusively well defined unsigned behavior, but my changes are too aggressive, and I'd like to introduce them gradually to give a chance of reviewing them.

------------------

While at it, use cCorceSimple:to: 'unsigned int' when fetching integerValueOf rather than asUnsignedInteger.
The reason is that the first will never do sign extension, while the second would in 64bits.
OK, the 64bits spur cannot take this path, because a 32bit int would be a SmallInteger, but I prefer to throw good basis, this will avoid having to ask myelf about the same problem again in a couple of years...

I would much prefer to have a fetchUnsigned32/64, but we'll see that another time.

=============== Diff against VMMaker.oscog-nice.1735 ===============

Item was changed:
  ----- Method: InterpreterPrimitives>>positiveMachineIntegerValueOf: (in category 'primitive support') -----
  positiveMachineIntegerValueOf: oop
  	"Answer a value of an integer in address range, i.e up to the size of a machine word.
  	The object may be either a positive SmallInteger or a LargePositiveInteger of size <= word size."
  	<returnTypeC: #'unsigned long'>
  	<inline: true> "only two callers & one is primitiveNewWithArg"
  	| value bs ok |
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[value := objectMemory integerValueOf: oop.
  		 value < 0 ifTrue: [^self primitiveFail].
  		^value].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory
  			isClassOfNonImm: oop
  			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok ifFalse:
  		[self primitiveFail.
  		 ^0].
  	bs := objectMemory numBytesOfBytes: oop.
  	bs > (self sizeof: #'unsigned long') ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	((self sizeof: #'unsigned long') = 8
  	and: [bs > 4]) ifTrue:
  		[^self cppIf: VMBIGENDIAN
  			ifTrue:
  				[    (objectMemory fetchByte: 0 ofObject: oop)
  				 + ((objectMemory fetchByte: 1 ofObject: oop) <<  8)
  				 + ((objectMemory fetchByte: 2 ofObject: oop) << 16)
  				 + ((objectMemory fetchByte: 3 ofObject: oop) << 24)
  				 + ((objectMemory fetchByte: 4 ofObject: oop) << 32)
  				 + ((objectMemory fetchByte: 5 ofObject: oop) << 40)
  				 + ((objectMemory fetchByte: 6 ofObject: oop) << 48)
  				 + ((objectMemory fetchByte: 7 ofObject: oop) << 56)]
  			ifFalse:
  				[objectMemory fetchLong64: 0 ofObject: oop]]
  		ifFalse:
  			[^self cppIf: VMBIGENDIAN
  				ifTrue:
  					[    (objectMemory fetchByte: 0 ofObject: oop)
  					 + ((objectMemory fetchByte: 1 ofObject: oop) <<  8)
  					 + ((objectMemory fetchByte: 2 ofObject: oop) << 16)
  					 + ((objectMemory fetchByte: 3 ofObject: oop) << 24)]
  				ifFalse:
+ 					[self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int']]!
- 					[objectMemory fetchLong32: 0 ofObject: oop]]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitAnd (in category 'arithmetic integer primitives') -----
  primitiveBitAnd
  	<inline: false>
+ 	<var: 'integerArgumentValue' type: #usqInt>
+ 	<var: 'intergerReceiverValue' type: #usqInt>
+ 	| integerReceiver integerArgument integerArgumentValue integerReceiverValue |
- 	<var: 'integerArgument' type: #usqInt>
- 	<var: 'intergerReceiver' type: #usqInt>
- 	| integerReceiver integerArgument |
  	integerArgument := self stackTop.
  	integerReceiver := self stackValue: 1.
  	"Comment out the short-cut.  Either the inline interpreter bytecode or the JIT primitive will handle this case.
  	 ((objectMemory isIntegerObject: integerArgument)
  	 and: [objectMemory isIntegerObject: integerReceiver])
  		ifTrue: [self pop: 2 thenPush: (integerArgument bitAnd: integerReceiver)]
  		ifFalse:
  			["
+ 			integerArgumentValue := self positiveMachineIntegerValueOf: integerArgument.
+ 			integerReceiverValue := self positiveMachineIntegerValueOf: integerReceiver.
- 			integerArgument := self positiveMachineIntegerValueOf: integerArgument.
- 			integerReceiver := self positiveMachineIntegerValueOf: integerReceiver.
  			self successful ifTrue:
+ 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitAnd: integerReceiverValue))]
- 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgument bitAnd: integerReceiver))]
  				ifFalse:
  					[]"]"!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitOr (in category 'arithmetic integer primitives') -----
  primitiveBitOr
  	<inline: false>
+ 	<var: 'integerArgumentValue' type: #usqInt>
+ 	<var: 'intergerReceiverValue' type: #usqInt>
+ 	| integerReceiver integerArgument integerArgumentValue integerReceiverValue |
- 	<var: 'integerArgument' type: #usqInt>
- 	<var: 'intergerReceiver' type: #usqInt>
- 	| integerReceiver integerArgument |
  	integerArgument := self stackTop.
  	integerReceiver := self stackValue: 1.
  	"Comment out the short-cut.  Either the inline interpreter bytecode or the JIT primitive will handle this case.
  	 ((objectMemory isIntegerObject: integerArgument)
  	 and: [objectMemory isIntegerObject: integerReceiver])
  		ifTrue: [self pop: 2 thenPush: (integerArgument bitOr: integerReceiver)]
  		ifFalse:
  			["
+ 			integerArgumentValue := self positiveMachineIntegerValueOf: integerArgument.
+ 			integerReceiverValue := self positiveMachineIntegerValueOf: integerReceiver.
- 			integerArgument := self positiveMachineIntegerValueOf: integerArgument.
- 			integerReceiver := self positiveMachineIntegerValueOf: integerReceiver.
  			self successful ifTrue:
+ 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitOr: integerReceiverValue))]
- 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgument bitOr: integerReceiver))]
  				ifFalse:
  					[]"]"!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitXor (in category 'arithmetic integer primitives') -----
  primitiveBitXor
  	<inline: false>
+ 	<var: 'integerArgumentValue' type: #usqInt>
+ 	<var: 'intergerReceiverValue' type: #usqInt>
+ 	| integerReceiver integerArgument integerArgumentValue integerReceiverValue |
- 	| integerReceiver integerArgument |
  	integerArgument := self stackTop.
  	integerReceiver := self stackValue: 1.
  	((objectMemory isIntegerObject: integerArgument)
  	 and: [objectMemory isIntegerObject: integerReceiver])
  		ifTrue: "xoring will leave the tag bits zero, whether the tag is 1 or zero, so add it back in."
  			[self pop: 2 thenPush: (integerArgument bitXor: integerReceiver) + objectMemory smallIntegerTag]
  		ifFalse:
+ 			[integerArgumentValue := self positiveMachineIntegerValueOf: integerArgument.
+ 			integerReceiverValue := self positiveMachineIntegerValueOf: integerReceiver.
- 			[integerArgument := self positiveMachineIntegerValueOf: integerArgument.
- 			 integerReceiver := self positiveMachineIntegerValueOf: integerReceiver.
  			 self successful ifTrue:
+ 				[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitXor: integerReceiverValue))]]!
- 				[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgument bitXor: integerReceiver))]]!

Item was changed:
  ----- Method: InterpreterPrimitives>>signed64BitValueOf: (in category 'primitive support') -----
  signed64BitValueOf: oop
  	"Convert the given object into an integer value.
  	 The object may be either a positive SmallInteger or a eight-byte LargeInteger."
  	| sz value negative ok magnitude |
  	<inline: false>
  	<returnTypeC: #sqLong>
  	<var: #value type: #sqLong>
  	<var: #magnitude type: #usqLong>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^self cCoerce: (objectMemory integerValueOf: oop) to: #sqLong].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifTrue: [negative := false]
  		ifFalse:
  			[negative := true.
  			 ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse:
  				[self primitiveFail.
  				 ^0]].
  	sz := objectMemory numBytesOfBytes: oop.
  	sz > (self sizeof: #sqLong) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	self cppIf: VMBIGENDIAN
  		ifTrue:
  			[magnitude := objectMemory fetchByte: sz - 1 ofObject: oop.
  			 sz - 2 to: 0 by: -1 do: [:i |
  				magnitude := magnitude << 8 + (objectMemory fetchByte: i ofObject: oop)]]
  		ifFalse:
  			[magnitude := sz > 4
  						ifTrue: [objectMemory fetchLong64: 0 ofObject: oop]
+ 						ifFalse: [self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int']].
- 						ifFalse: [(objectMemory fetchLong32: 0 ofObject: oop) asUnsignedInteger]].
  
  	(negative
  		ifTrue: [magnitude > 16r8000000000000000]
  		ifFalse: [magnitude >= 16r8000000000000000])
  			ifTrue: [self primitiveFail.
  				^0].
  	negative
  		ifTrue: [value := 0 - magnitude]
  		ifFalse: [value := magnitude].
  	^value!



More information about the Vm-dev mailing list