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

commits at source.squeak.org commits at source.squeak.org
Wed Mar 23 18:13:31 UTC 2016


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

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

Name: VMMaker.oscog-eem.1737
Author: eem
Time: 23 March 2016, 11:11:50.230844 am
UUID: b6c433f3-b377-4fb3-9547-6e6bd24eb90d
Ancestors: VMMaker.oscog-nice.1736

Review VMMaker.oscog-nice.1731 through VMMaker.oscog-nice.1736.

Fix maybeInlinePositive32BitIntegerFor: & positive64BitIntegerFor: in simulation for negative integers less than minSmallInteger.
Shorten the commentary in the streamlined bitAnd: and bitOr: primitives.

Use the right convention for SpurMemoryManager>>stSizeOf:; we mist defer to the coInterpreter so that the right code is run when simulating.

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

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 |
  	integerArgument := self stackTop.
  	integerReceiver := self stackValue: 1.
+ 	"Note no short-cut for SmallIntegers.  Either the inline interpreter bytecode or the JIT primitive will handle this case."
+ 	integerArgumentValue := self positiveMachineIntegerValueOf: integerArgument.
+ 	integerReceiverValue := self positiveMachineIntegerValueOf: integerReceiver.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitAnd: integerReceiverValue))]!
- 	"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.
- 			self successful ifTrue:
- 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitAnd: integerReceiverValue))]
- 				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 |
  	integerArgument := self stackTop.
  	integerReceiver := self stackValue: 1.
+ 	"Note no short-cut for SmallIntegers.  Either the inline interpreter bytecode or the JIT primitive will handle this case."
+ 	integerArgumentValue := self positiveMachineIntegerValueOf: integerArgument.
+ 	integerReceiverValue := self positiveMachineIntegerValueOf: integerReceiver.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitOr: integerReceiverValue))]!
- 	"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.
- 			self successful ifTrue:
- 					[self pop: 2 thenPush: (self positiveMachineIntegerFor: (integerArgumentValue bitOr: integerReceiverValue))]
- 				ifFalse:
- 					[]"]"!

Item was changed:
  ----- Method: SpurMemoryManager>>stSizeOf: (in category 'object access') -----
  stSizeOf: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	"Return the number of indexable fields in the receiver"
  	<doNotGenerate>
+ 	^coInterpreter stSizeOf: oop!
- 	^oop basicSize!

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
  	"N.B. will *not* cause a GC.
  	 integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
  	<notOption: #Spur64BitMemoryManager>
  	<var: 'integerValue' type: #'unsigned int'>
  	| newLargeInteger |
  	self deny: objectMemory hasSixtyFourBitImmediates.
         "force coercion because slang inliner sometimes incorrectly pass a signed int without converting to unsigned"
+        (self cCode: [self cCoerceSimple: integerValue to: #'unsigned int']
+ 			inSmalltalk: [integerValue bitAnd: 1 << 32 - 1]) <= objectMemory maxSmallInteger ifTrue:
+ 		[^objectMemory integerObjectOf: integerValue].
-        (self cCoerceSimple: integerValue to: #'unsigned int') <= objectMemory maxSmallInteger
- 		ifTrue: [^ objectMemory integerObjectOf: integerValue].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
  	self cppIf: VMBIGENDIAN
  		ifTrue:
  			[objectMemory
  				storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
  				storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
  				storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
  				storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF)]
  		ifFalse:
  			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: integerValue].
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>positive64BitIntegerFor: (in category 'primitive support') -----
  positive64BitIntegerFor: integerValue
  	<api>
  	<var: 'integerValue' type: #usqLong>
  	<var: 'highWord' type: #'unsigned int'>
  	"Answer a Large Positive Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger highWord sz |
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
+ 			[(self cCode: [integerValue] inSmalltalk: [integerValue bitAnd: 1 << 64 - 1]) <= objectMemory maxSmallInteger ifTrue:
- 			[integerValue <= objectMemory maxSmallInteger ifTrue:
  				[^objectMemory integerObjectOf: integerValue].
  			 sz := 8]
  		ifFalse:
  			[(highWord := integerValue >> 32) = 0 ifTrue:
  				[^self positive32BitIntegerFor: integerValue].
  			 sz := 5.
  			 (highWord := highWord >> 8) = 0 ifFalse:
  				[sz := sz + 1.
  				 (highWord := highWord >> 8) = 0 ifFalse:
  					[sz := sz + 1.
  					 (highWord := highWord >> 8) = 0 ifFalse:[sz := sz + 1]]]].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: 8 / objectMemory bytesPerOop.
  	self cppIf: VMBIGENDIAN
  		ifTrue:
  			[objectMemory
  				storeByte: 7 ofObject: newLargeInteger withValue: (integerValue >> 56 bitAnd: 16rFF);
  				storeByte: 6 ofObject: newLargeInteger withValue: (integerValue >> 48 bitAnd: 16rFF);
  				storeByte: 5 ofObject: newLargeInteger withValue: (integerValue >> 40 bitAnd: 16rFF);
  				storeByte: 4 ofObject: newLargeInteger withValue: (integerValue >> 32 bitAnd: 16rFF);
  				storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
  				storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
  				storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
  				storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF)]
  		ifFalse:
  			[objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: integerValue].
  	^newLargeInteger
  !



More information about the Vm-dev mailing list