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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 15 21:46:05 UTC 2016


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

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

Name: VMMaker.oscog-eem.1636
Author: eem
Time: 15 January 2016, 1:44:19.712356 pm
UUID: b30fe4bc-4de8-4dde-9709-3ad459f46862
Ancestors: VMMaker.oscog-eem.1635

Add 16-bit indexability to Spur.  Generate slimmer code for positive32BitValueOf: on 64-bit Spur.

Fix a slip in commonAtPut: immutability testing.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>positive32BitValueOf: (in category 'primitive support') -----
  positive32BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or a four-byte LargePositiveInteger."
  	<returnTypeC: #usqInt>
  	| value ok sz |
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[value := objectMemory integerValueOf: oop.
  		 (value < 0
  		  or: [objectMemory wordSize > 4
  		  and: [self cCode: [(self cCoerceSimple: value to: #'unsigned int') ~= value]
  					inSmalltalk: [value >> 32 ~= 0]]]) ifTrue:
  			[self primitiveFail. value := 0].
  		 ^value].
  
+ 	(objectMemory hasSixtyFourBitImmediates
+ 	 or: [objectMemory isNonIntegerImmediate: oop])
- 	(objectMemory isNonIntegerImmediate: oop) ifTrue:
- 		[self primitiveFail.
- 		 ^0].
- 
- 	ok := objectMemory
- 			isClassOfNonImm: oop
- 			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
- 			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
- 	ok ifFalse:
- 		[self primitiveFail.
- 		 ^0].
- 	sz := objectMemory numBytesOfBytes: oop.
- 	sz > 4 ifTrue:
- 		[self primitiveFail.
- 		 ^0].
- 	^self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			[self primitiveFail.
+ 			 ^0]
- 			[   (objectMemory fetchByte: 0 ofObject: oop)
- 			+ ((objectMemory fetchByte: 1 ofObject: oop) <<  8)
- 			+ ((objectMemory fetchByte: 2 ofObject: oop) << 16)
- 			+ ((objectMemory fetchByte: 3 ofObject: oop) << 24)]
  		ifFalse:
+ 			[ok := objectMemory
+ 					isClassOfNonImm: oop
+ 					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
+ 					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
+ 			ok ifFalse:
+ 				[self primitiveFail.
+ 				 ^0].
+ 			sz := objectMemory numBytesOfBytes: oop.
+ 			sz > 4 ifTrue:
+ 				[self primitiveFail.
+ 				 ^0].
+ 			^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:
+ 					[objectMemory fetchLong32: 0 ofObject: oop]]!
- 			[objectMemory fetchLong32: 0 ofObject: oop]!

Item was changed:
  ----- Method: StackInterpreter>>commonAtPut: (in category 'indexing primitive support') -----
  commonAtPut: stringy
  	"This code is called if the receiver responds primitively to at:Put:.
  	 N.B. this does *not* use the at cache, instead inlining stObject:at:put:.
  	 Using the at cache here would require that callers set messageSelector
  	 and lkupClass and that is onerous and error-prone, and in any case,
  	 inlining produces much better performance than using the at cache here."
+ 	| value index rcvr |
- 	| value index rcvr badRcvr |
  	<inline: true> "to get it inlined in primitiveAtPut and primitiveStringAtPut"
  	self initPrimCall.
  	rcvr := self stackValue: 2.
  	index := self stackValue: 1.
  	value := self stackTop.
+ 	(objectMemory isImmediate: rcvr) ifTrue:
- 	self cppIf: IMMUTABILITY 
- 		ifTrue: [ badRcvr := objectMemory isOopImmutable: rcvr ]
- 		ifFalse: [ badRcvr := objectMemory isImmediate: rcvr ].
- 	badRcvr ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
  	"No need to test for large positive integers here.  No object has 1g elements"
  	((objectMemory isNonIntegerObject: index)
  	 or: [argumentCount > 2 "e.g. object:basicAt:put:"
  		 and: [objectMemory isForwarded: rcvr]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	self cppIf: IMMUTABILITY ifTrue:
+ 		[(objectMemory isImmutable: rcvr) ifTrue:
+ 			[^self primitiveFailFor: PrimErrNoModification]].
  	index := objectMemory integerValueOf: index.
  	stringy
  		ifTrue: [self stObject: rcvr at: index put: (self asciiOfCharacter: value)]
  		ifFalse: [self stObject: rcvr at: index put: value].
  	self successful ifTrue:
  		[self pop: argumentCount+1 thenPush: value]!

Item was changed:
  ----- Method: StackInterpreter>>subscript:with:format: (in category 'indexing primitive support') -----
  subscript: array with: index format: fmt
  	"Note: This method assumes that the index is within bounds!!"
  
  	<inline: true>
  	fmt <= objectMemory lastPointerFormat ifTrue:
  		[^objectMemory fetchPointer: index - 1 ofObject: array].
  	fmt >= objectMemory firstByteFormat ifTrue:
  		[^objectMemory integerObjectOf:
  			(objectMemory fetchByte: index - 1 ofObject: array)].
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
+ 		[^objectMemory integerObjectOf:
+ 			(objectMemory fetchShort16: index - 1 ofObject: array)].
+ 	"double-word type objects; for now assume no 64-bit indexable objects"
- 	"long-word type objects"
  	^self positive32BitIntegerFor:
  			(objectMemory fetchLong32: index - 1 ofObject: array)!

Item was changed:
  ----- Method: StackInterpreter>>subscript:with:storing:format: (in category 'indexing primitive support') -----
  subscript: array with: index storing: oopToStore format: fmt 
  	"Note: This method assumes that the index is within bounds!!"
+ 	| signedValueToStore unsignedValueToStore |
- 	| valueToStore |
  	<inline: true>
+ 	fmt <= objectMemory lastPointerFormat ifTrue:
+ 		[objectMemory storePointer: index - 1 ofObject: array withValue: oopToStore.
+ 		 ^self].
+ 	fmt >= objectMemory firstByteFormat ifTrue:
+ 		[(objectMemory isIntegerObject: oopToStore) ifFalse:
+ 			[primFailCode := PrimErrBadArgument.
+ 			 ^self].
+ 		 signedValueToStore := objectMemory integerValueOf: oopToStore.
+ 		 (signedValueToStore >= 0 and: [signedValueToStore <= 255]) ifFalse:
+ 			[primFailCode := PrimErrBadArgument.
+ 			 ^self].
+ 		 objectMemory storeByte: index - 1 ofObject: array withValue: signedValueToStore.
+ 		 ^self].
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
+ 		[(objectMemory isIntegerObject: oopToStore) ifFalse:
+ 			[primFailCode := PrimErrBadArgument.
+ 			 ^self].
+ 		 signedValueToStore := objectMemory integerValueOf: oopToStore.
+ 		 (signedValueToStore >= 0 and: [signedValueToStore <= 65535]) ifFalse:
+ 			[primFailCode := PrimErrBadArgument.
+ 			 ^self].
+ 		 objectMemory storeShort16: index - 1 ofObject: array withValue: signedValueToStore.
+ 		 ^self].
+ 	"double-word type objects; for now assume no 64-bit indexable objects"
+ 	unsignedValueToStore := self positive32BitValueOf: oopToStore.
+ 	self successful ifTrue:
+ 		[objectMemory storeLong32: index - 1 ofObject: array withValue: unsignedValueToStore]!
- 	fmt <= objectMemory lastPointerFormat
- 		ifTrue:
- 			[objectMemory
- 				storePointer: index - 1
- 				ofObject: array
- 				withValue: oopToStore]
- 		ifFalse:
- 			[fmt >= objectMemory firstByteFormat
- 				ifTrue:
- 					[(objectMemory isIntegerObject: oopToStore) ifFalse:
- 						[primFailCode := PrimErrBadIndex].
- 					 valueToStore := objectMemory integerValueOf: oopToStore.
- 					 (valueToStore >= 0 and: [valueToStore <= 255]) ifFalse:
- 						[primFailCode := PrimErrBadArgument].
- 					self successful ifTrue:
- 						[objectMemory
- 							storeByte: index - 1
- 							ofObject: array
- 							withValue: valueToStore]]
- 				ifFalse: "long-word type objects"
- 					[valueToStore := self positive32BitValueOf: oopToStore.
- 					self successful ifTrue:
- 						[objectMemory
- 							storeLong32: index - 1
- 							ofObject: array
- 							withValue: valueToStore]]]!



More information about the Vm-dev mailing list