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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 20 00:29:30 UTC 2014


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

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

Name: VMMaker.oscog-eem.944
Author: eem
Time: 19 November 2014, 4:26:08.21 pm
UUID: 14ad71a2-117d-4a73-b041-efb833d79f01
Ancestors: VMMaker.oscog-eem.943

Define areIntegers:and: for 64-bit Spur, and move it
into the ObjectMemory hierarchies.
Add maxSmallInteger and minSmallInteger and matching
manifest constants.  Use these in LargeIntegersPlugin
and Matrix2x3Plugin.

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

Item was added:
+ ----- Method: CCodeGenerator>>generateSmallIntegerConstant:on:indent: (in category 'C translation') -----
+ generateSmallIntegerConstant: aSendNode on: aStream indent: indent
+ 	aSendNode selector = #minSmallInteger ifTrue:
+ 		[^aStream nextPutAll: 'MinSmallInteger'].
+ 	aSendNode selector = #maxSmallInteger ifTrue:
+ 		[^aStream nextPutAll: 'MaxSmallInteger'].
+ 	self error: 'unknown SmallInteger constant'!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
  	#rounded			#generateRounded:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#addressOf:put:			#generateAddressOf:on:indent:
  	#asAddress:put:			#generateAsAddress:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asVoidPointer				#generateAsVoidPointer:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerOop 				#generateBytesPerOop:on:indent:
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#wordSize		 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
+ 	#minSmallInteger			#generateSmallIntegerConstant:on:indent:
+ 	#maxSmallInteger			#generateSmallIntegerConstant:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  	#value:value:value:					#generateValue:on:indent:
  
  	#deny:								#generateDeny:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was removed:
- ----- Method: Interpreter>>areIntegers:and: (in category 'utilities') -----
- areIntegers: oop1 and: oop2
- "Test oop1 and oop2 to make sure both are SmallIntegers."
- 	^ ((oop1 bitAnd: oop2) bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: InterpreterPrimitives>>magnitude64BitIntegerFor:neg: (in category 'primitive support') -----
  magnitude64BitIntegerFor: magnitude neg: isNegative
  	"Return a Large Integer object for the given integer magnitude and sign"
  	| newLargeInteger largeClass intValue highWord sz isSmall smallVal |
  	<var: 'magnitude' type: #usqLong>
  	<var: 'highWord' type: #usqInt>
  
  	isSmall := isNegative
+ 				ifTrue: [magnitude <= (objectMemory maxSmallInteger + 1)]
+ 				ifFalse: [magnitude < (objectMemory maxSmallInteger + 1)].
- 				ifTrue: [magnitude <= 16r40000000]
- 				ifFalse: [magnitude < 16r40000000].
  	isSmall ifTrue:
  		[smallVal := self cCoerceSimple: magnitude to: #sqInt.
  		isNegative	ifTrue: [smallVal := 0 - smallVal].
  		^objectMemory integerObjectOf: smallVal].
  	largeClass := isNegative
  					ifTrue: [objectMemory classLargeNegativeInteger]
  					ifFalse: [objectMemory classLargePositiveInteger].
  	highWord := magnitude >> 32.
  	highWord = 0 
  		ifTrue: [sz := 4] 
  		ifFalse:
  			[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 instantiateClass: largeClass indexableSize:  sz.
  	0 to: sz-1 do: [:i |
  		intValue := (magnitude >> (i * 8)) bitAnd: 255.
  		objectMemory storeByte: i ofObject: newLargeInteger withValue: intValue].
  	^newLargeInteger!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitShift (in category 'arithmetic integer primitives') -----
  primitiveBitShift 
  	| integerReceiver integerArgument shifted |
+ 	integerArgument := self stackTop.
+ 	(objectMemory isIntegerObject: integerArgument) ifFalse:
+ 		[^self primitiveFailed].
+ 	integerReceiver := self stackValue: 1.
+ 	objectMemory wordSize = 4
+ 		ifTrue:
+ 			[integerReceiver := self positive32BitValueOf: integerReceiver]
+ 		ifFalse:
+ 			[integerReceiver := self signed64BitValueOf: integerReceiver].
+ 	self successful ifTrue:
+ 		[(integerArgument := objectMemory integerValueOf: integerArgument) >= 0
+ 			ifTrue: "Left shift -- must fail if we lose bits beyond 32"
+ 				[integerArgument <= objectMemory numSmallIntegerBits ifFalse:
+ 					[^self primitiveFailed].
+ 				shifted := integerReceiver << integerArgument.
+ 				(shifted >> integerArgument) = integerReceiver ifFalse:
+ 					[^self primitiveFailed]]
+ 			ifFalse: "Right shift -- OK to lose bits"
+ 				[integerArgument >= objectMemory numSmallIntegerBits negated ifFalse:
+ 					[^self primitiveFailed].
+ 			shifted := integerReceiver >> (0 - integerArgument)].
+ 		shifted := (objectMemory isIntegerValue: shifted)
+ 					ifTrue: [objectMemory integerObjectOf: shifted]
+ 					ifFalse:
+ 						[objectMemory wordSize = 4
+ 							ifTrue: [self positive32BitIntegerFor: shifted]
+ 							ifFalse: [self signed64BitIntegerFor: shifted]].
+ 		self pop: 2 thenPush: shifted]!
- 	integerArgument := self popInteger.
- 	integerReceiver := self popPos32BitInteger.
- 	self successful ifTrue: [
- 		integerArgument >= 0 ifTrue: [
- 			"Left shift -- must fail if we lose bits beyond 32"
- 			self success: integerArgument <= 31.
- 			shifted := integerReceiver << integerArgument.
- 			self success: (shifted >> integerArgument) = integerReceiver.
- 		] ifFalse: [
- 			"Right shift -- OK to lose bits"
- 			self success: integerArgument >= -31.
- 			shifted := integerReceiver >> (0 - integerArgument).
- 		].
- 	].
- 	self successful
- 		ifTrue: [self push: (self positive32BitIntegerFor: shifted)]
- 		ifFalse: [self unPop: 2]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>cDigitLengthOfCSI: (in category 'C core util') -----
  cDigitLengthOfCSI: csi 
+ 	"Answer the number of bytes required to represent the value of a CSmallInteger."
+ 	csi >= 0 ifTrue:
+ 		[csi < 256 ifTrue:
+ 			[^1].
+ 		 csi < 65536 ifTrue:
+ 			[^2].
+ 		 csi < 16777216 ifTrue:
+ 			[^3].
+ 		 interpreterProxy bytesPerOop = 4
+ 			ifTrue:
+ 				[^4]
+ 			ifFalse:
+ 				[csi < 4294967296 ifTrue:
+ 					[^4].
+ 				 csi < 1099511627776 ifTrue:
+ 					[^5].
+ 				 csi < 281474976710656 ifTrue:
+ 					[^6].
+ 				 csi < 72057594037927936 ifTrue:
+ 					[^7].
+ 				 ^8]].
+ 	csi > -256 ifTrue:
+ 		[^1].
+ 	csi > -65536 ifTrue:
+ 		[^2].
+ 	csi > -16777216 ifTrue:
+ 		[^3].
+ 	interpreterProxy bytesPerOop = 4
+ 		ifTrue:
+ 			[^4]
+ 		ifFalse:
+ 			[csi > -4294967296 ifTrue:
+ 				[^4].
+ 			 csi > -1099511627776 ifTrue:
+ 				[^5].
+ 			 csi > -281474976710656 ifTrue:
+ 				[^6].
+ 			 csi > -72057594037927936 ifTrue:
+ 				[^7].
+ 			^8]!
- 	"Answer the number of indexable fields of a CSmallInteger. This value is 
- 	   the same as the largest legal subscript."
- 	(csi < 256 and: [csi > -256])
- 		ifTrue: [^ 1].
- 	(csi < 65536 and: [csi > -65536])
- 		ifTrue: [^ 2].
- 	(csi < 16777216 and: [csi > -16777216])
- 		ifTrue: [^ 3].
- 	^ 4!

Item was changed:
  ----- Method: LargeIntegersPlugin>>cDigitOfCSI:at: (in category 'C core util') -----
  cDigitOfCSI: csi at: ix 
  	"Answer the value of an indexable field in the receiver.              
  	LargePositiveInteger uses bytes of base two number, and each is a       
  	      'digit' base 256."
  	"ST indexed!!"
+ 	ix < 1 ifTrue: [interpreterProxy primitiveFail. ^0].
+ 	ix > interpreterProxy bytesPerOop ifTrue: [^0].
+ 	^self
+ 		cCode: [(csi < 0
+ 					ifTrue: [0 - csi]
+ 					ifFalse: [csi]) >> (ix - 1 * 8) bitAnd: 255]
+ 		inSmalltalk: [csi digitAt: ix]!
- 	ix < 1 ifTrue: [interpreterProxy primitiveFail].
- 	ix > 4 ifTrue: [^ 0].
- 	csi < 0
- 		ifTrue: 
- 			[self cCode: ''
- 				inSmalltalk: [csi = -1073741824 ifTrue: ["SmallInteger minVal"
- 						"Can't negate minVal -- treat specially"
- 						^ #(0 0 0 64 ) at: ix]].
- 			^ (0 - csi) >> (ix - 1 * 8)
- 				bitAnd: 255]
- 		ifFalse: [^ csi >> (ix - 1 * 8)
- 				bitAnd: 255]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>createLargeFromSmallInteger: (in category 'oop util') -----
  createLargeFromSmallInteger: anOop 
  	"anOop has to be a SmallInteger!!"
+ 	| val class size res pByte byte |
- 	| val class size res pByte |
  	<var: #pByte type: 'unsigned char *  '>
  	val := interpreterProxy integerValueOf: anOop.
  	val < 0
  		ifTrue: [class := interpreterProxy classLargeNegativeInteger]
  		ifFalse: [class := interpreterProxy classLargePositiveInteger].
  	size := self cDigitLengthOfCSI: val.
  	res := interpreterProxy instantiateClass: class indexableSize: size.
  	pByte := interpreterProxy firstIndexableField: res.
+ 	1 to: size do: [:ix |
+ 		byte := self cDigitOfCSI: val at: ix.
+ 		pByte at: ix - 1 put: byte].
+ 	^res!
- 	1 to: size do: [:ix | pByte at: ix - 1 put: (self cDigitOfCSI: val at: ix)].
- 	^ res!

Item was changed:
  ----- Method: LargeIntegersPlugin>>isNormalized: (in category 'oop functions') -----
  isNormalized: anInteger 
  	| len maxVal minVal sLen class positive |
  	(interpreterProxy isIntegerObject: anInteger) ifTrue:
  		[^ true].
  	class := interpreterProxy fetchClassOf: anInteger.
  	(positive := class = interpreterProxy classLargePositiveInteger) ifFalse:
  		[class = interpreterProxy classLargeNegativeInteger ifFalse:
  			[interpreterProxy primitiveFailFor: PrimErrBadArgument.
  			 ^false]].
  	"Check for leading zero of LargeInteger"
  	len := self digitLength: anInteger.
  	len = 0 ifTrue:
  		[^ false].
  	(self unsafeByteOf: anInteger at: len) = 0 ifTrue:
  		[^ false].
  	"no leading zero, now check if anInteger is in SmallInteger range or not"
+ 	sLen := interpreterProxy bytesPerOop.
- 	sLen := 4.
  	"maximal digitLength of aSmallInteger"
  	len > sLen ifTrue:
  		[^ true].
  	len < sLen ifTrue:
  		[^ false].
  	"len = sLen"
  	positive
+ 		ifTrue: [maxVal := interpreterProxy maxSmallInteger. "SmallInteger maxVal"
- 		ifTrue: [maxVal := 1073741823. "SmallInteger maxVal"
  				"all bytes of maxVal but the highest one are just FF's"
  				^ (self unsafeByteOf: anInteger at: sLen)
  					> (self cDigitOfCSI: maxVal at: sLen)]
+ 		ifFalse: [minVal := interpreterProxy minSmallInteger. "SmallInteger minVal"
- 		ifFalse: [minVal := -1073741824. "SmallInteger minVal"
  				"all bytes of minVal but the highest one are just 00's"
  			(self unsafeByteOf: anInteger at: sLen) < (self cDigitOfCSI: minVal at: sLen) ifTrue:
  				[^ false].
  			"if just one digit differs, then anInteger < minval (the corresponding digit byte is greater!!)
  			and therefore a LargeNegativeInteger"
  			1
  				to: sLen
  				do: [:ix |
  					(self unsafeByteOf: anInteger at: ix) = (self cDigitOfCSI: minVal at: ix) ifFalse:
  						[^ true]]].
  	^ false!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizeNegative: (in category 'oop functions') -----
  normalizeNegative: aLargeNegativeInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| sLen val len oldLen minVal |
  	len := oldLen := self digitLength: aLargeNegativeInteger.
  	[len ~= 0 and: [(self unsafeByteOf: aLargeNegativeInteger at: len)
  			= 0]]
  		whileTrue: [len := len - 1].
  	len = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
  	sLen := 4.
  	"SmallInteger minVal digitLength"
  	len <= sLen
  		ifTrue: 
  			["SmallInteger minVal"
+ 			minVal := interpreterProxy minSmallInteger.
- 			minVal := -1073741824.
  			(len < sLen or: [(self digitOfBytes: aLargeNegativeInteger at: sLen)
  					< (self cDigitOfCSI: minVal at: sLen)
  				"minVal lastDigit"])
  				ifTrue: 
  					["If high digit less, then can be small"
  					val := 0.
  					len
  						to: 1
  						by: -1
  						do: [:i | val := val * 256 - (self unsafeByteOf: aLargeNegativeInteger at: i)].
  					^ val asOop: SmallInteger].
  			1 to: sLen do: [:i | "If all digits same, then = minVal (sr: minVal digits 1 to 3 are 
  				          0)"
  				(self digitOfBytes: aLargeNegativeInteger at: i)
  					= (self cDigitOfCSI: minVal at: i)
  					ifFalse: ["Not so; return self shortened"
  						len < oldLen
  							ifTrue: ["^ self growto: len"
  								^ self bytes: aLargeNegativeInteger growTo: len]
  							ifFalse: [^ aLargeNegativeInteger]]].
  			^ minVal asOop: SmallInteger].
  	"Return self, or a shortened copy"
  	len < oldLen
  		ifTrue: ["^ self growto: len"
  			^ self bytes: aLargeNegativeInteger growTo: len]
  		ifFalse: [^ aLargeNegativeInteger]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizePositive: (in category 'oop functions') -----
  normalizePositive: aLargePositiveInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| sLen val len oldLen |
  	len := oldLen := self digitLength: aLargePositiveInteger.
  	[len ~= 0 and: [(self unsafeByteOf: aLargePositiveInteger at: len)
  			= 0]]
  		whileTrue: [len := len - 1].
  	len = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
+ 	sLen := interpreterProxy bytesPerOop.
- 	sLen := 4.
  	"SmallInteger maxVal digitLength."
+ 	(len <= sLen
+ 	 and: [(self digitOfBytes: aLargePositiveInteger at: sLen)
+ 			<= (self cDigitOfCSI: interpreterProxy maxSmallInteger at: sLen)
- 	(len <= sLen and: [(self digitOfBytes: aLargePositiveInteger at: sLen)
- 			<= (self cDigitOfCSI: 1073741823 at: sLen)
  		"SmallInteger maxVal"])
  		ifTrue: 
  			["If so, return its SmallInt value"
  			val := 0.
  			len
  				to: 1
  				by: -1
  				do: [:i | val := val * 256 + (self unsafeByteOf: aLargePositiveInteger at: i)].
  			^ val asOop: SmallInteger].
  	"Return self, or a shortened copy"
  	len < oldLen
  		ifTrue: ["^ self growto: len"
  			^ self bytes: aLargePositiveInteger growTo: len]
  		ifFalse: [^ aLargePositiveInteger]!

Item was changed:
  ----- Method: Matrix2x3Plugin>>okayIntValue: (in category 'private') -----
  okayIntValue: value
+ 	^(value >= interpreterProxy minSmallInteger asFloat
+ 	  and: [m23ResultX <= interpreterProxy maxSmallInteger asFloat])!
- 	^(value >= -1073741824 asFloat and:[m23ResultX <= 1073741823 asFloat]) 
- !

Item was removed:
- ----- Method: NewspeakInterpreter>>areIntegers:and: (in category 'utilities') -----
- areIntegers: oop1 and: oop2
- "Test oop1 and oop2 to make sure both are SmallIntegers."
- 	^ ((oop1 bitAnd: oop2) bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: ObjectMemory>>areIntegers:and: (in category 'interpreter access') -----
+ areIntegers: oop1 and: oop2
+ 	"Test oop1 and oop2 to make sure both are SmallIntegers."
+ 	^((oop1 bitAnd: oop2) bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: ObjectMemory>>maxSmallInteger (in category 'interpreter access') -----
+ maxSmallInteger
+ 	^1073741823!

Item was added:
+ ----- Method: ObjectMemory>>minSmallInteger (in category 'interpreter access') -----
+ minSmallInteger
+ 	^-1073741824!

Item was added:
+ ----- Method: ObjectMemory>>numSmallIntegerBits (in category 'interpreter access') -----
+ numSmallIntegerBits
+ 	^31!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>areIntegers:and: (in category 'interpreter access') -----
+ areIntegers: oop1 and: oop2
+ 	"Test oop1 and oop2 to make sure both are SmallIntegers."
+ 	^((oop1 bitAnd: oop2) bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>maxSmallInteger (in category 'interpreter access') -----
+ maxSmallInteger
+ 	^16r3FFFFFFF!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>minSmallInteger (in category 'interpreter access') -----
+ minSmallInteger
+ 	^-16r40000000!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>numSmallIntegerBits (in category 'interpreter access') -----
+ numSmallIntegerBits
+ 	^31!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>fetchFloatAt:into: (in category 'float primitives') -----
  fetchFloatAt: floatBitsAddress into: aFloat
+ 	aFloat at: 2 put: (self long32At: floatBitsAddress).
+ 	aFloat at: 1 put: (self long32At: floatBitsAddress+4)!
- 	aFloat at: 1 put: (self long64At: floatBitsAddress)!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>areIntegers:and: (in category 'interpreter access') -----
+ areIntegers: oop1 and: oop2
+ 	"Test oop1 and oop2 to make sure both are SmallIntegers."
+ 	^(self isIntegerObject: oop1)
+ 	  and: [self isIntegerObject: oop2]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>maxSmallInteger (in category 'interpreter access') -----
+ maxSmallInteger
+ 	^16rFFFFFFFFFFFFFFF!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>minSmallInteger (in category 'interpreter access') -----
+ minSmallInteger
+ 	^-16r1000000000000000!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>numSmallIntegerBits (in category 'interpreter access') -----
+ numSmallIntegerBits
+ 	^61!

Item was added:
+ ----- Method: SpurMemoryManager>>areIntegers:and: (in category 'interpreter access') -----
+ areIntegers: oop1 and: oop2
+ 	"Test oop1 and oop2 to make sure both are SmallIntegers."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>minSmallInteger (in category 'interpreter access') -----
+ minSmallInteger
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>numSmallIntegerBits (in category 'interpreter access') -----
+ numSmallIntegerBits
+ 	self subclassResponsibility!

Item was removed:
- ----- Method: StackInterpreter>>areIntegers:and: (in category 'utilities') -----
- areIntegers: oop1 and: oop2
- "Test oop1 and oop2 to make sure both are SmallIntegers."
- 	^ ((oop1 bitAnd: oop2) bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimAdd (in category 'common selector sends') -----
  bytecodePrimAdd
  	| rcvr arg result |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [result := (objectMemory integerValueOf: rcvr) + (objectMemory integerValueOf: arg).
  				(objectMemory isIntegerValue: result) ifTrue:
  					[self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
  					^ self fetchNextBytecode "success"]]
  		ifFalse: [self initPrimCall.
  				self externalizeIPandSP.
  				self primitiveFloatAdd: rcvr toArg: arg.
  				self internalizeIPandSP.
  				self successful ifTrue: [^ self fetchNextBytecode "success"]].
  
  	messageSelector := self specialSelector: 0.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimDivide (in category 'common selector sends') -----
  bytecodePrimDivide
  	| rcvr arg result |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [rcvr := objectMemory integerValueOf: rcvr.
  			arg := objectMemory integerValueOf: arg.
  			(arg ~= 0 and: [rcvr \\ arg = 0])
  				ifTrue: [result := rcvr // arg.
  					"generates C / operation"
  					(objectMemory isIntegerValue: result)
  						ifTrue: [self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
  							^ self fetchNextBytecode"success"]]]
  		ifFalse: [self initPrimCall.
  			self externalizeIPandSP.
  			self primitiveFloatDivide: rcvr byArg: arg.
  			self internalizeIPandSP.
  			self successful ifTrue: [^ self fetchNextBytecode"success"]].
  
  	messageSelector := self specialSelector: 9.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimEqual (in category 'common selector sends') -----
  bytecodePrimEqual
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheat: rcvr = arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheat: rcvr = arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheat: aBool].
  
  	messageSelector := self specialSelector: 6.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimEqualSistaV1 (in category 'common selector sends') -----
  bytecodePrimEqualSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr = arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr = arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
  
  	messageSelector := self specialSelector: 6.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimEqualV4 (in category 'common selector sends') -----
  bytecodePrimEqualV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatV4: rcvr = arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatV4: rcvr = arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatV4: aBool].
  
  	messageSelector := self specialSelector: 6.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterOrEqual (in category 'common selector sends') -----
  bytecodePrimGreaterOrEqual
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheat: rcvr >= arg]
  			inSmalltalk: [self booleanCheat: (objectMemory integerValueOf: rcvr) >= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreaterOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheat: aBool].
  
  	messageSelector := self specialSelector: 5.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterOrEqualSistaV1 (in category 'common selector sends') -----
  bytecodePrimGreaterOrEqualSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatSistaV1: rcvr >= arg]
  			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) >= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreaterOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
  
  	messageSelector := self specialSelector: 5.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterOrEqualV4 (in category 'common selector sends') -----
  bytecodePrimGreaterOrEqualV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatV4: rcvr >= arg]
  			inSmalltalk: [self booleanCheatV4: (objectMemory integerValueOf: rcvr) >= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreaterOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatV4: aBool].
  
  	messageSelector := self specialSelector: 5.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterThan (in category 'common selector sends') -----
  bytecodePrimGreaterThan
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheat: rcvr > arg]
  			inSmalltalk: [self booleanCheat: (objectMemory integerValueOf: rcvr) > (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreater: rcvr thanArg: arg.
  	self successful ifTrue: [^self booleanCheat: aBool].
  
  	messageSelector := self specialSelector: 3.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterThanSistaV1 (in category 'common selector sends') -----
  bytecodePrimGreaterThanSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatSistaV1: rcvr > arg]
  			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) > (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreater: rcvr thanArg: arg.
  	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
  
  	messageSelector := self specialSelector: 3.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimGreaterThanV4 (in category 'common selector sends') -----
  bytecodePrimGreaterThanV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatV4: rcvr > arg]
  			inSmalltalk: [self booleanCheatV4: (objectMemory integerValueOf: rcvr) > (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatGreater: rcvr thanArg: arg.
  	self successful ifTrue: [^self booleanCheatV4: aBool].
  
  	messageSelector := self specialSelector: 3.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessOrEqual (in category 'common selector sends') -----
  bytecodePrimLessOrEqual
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheat: rcvr <= arg]
  			inSmalltalk: [self booleanCheat: (objectMemory integerValueOf: rcvr) <= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLessOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheat: aBool].
  
  	messageSelector := self specialSelector: 4.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessOrEqualSistaV1 (in category 'common selector sends') -----
  bytecodePrimLessOrEqualSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatSistaV1: rcvr <= arg]
  			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) <= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLessOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
  
  	messageSelector := self specialSelector: 4.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessOrEqualV4 (in category 'common selector sends') -----
  bytecodePrimLessOrEqualV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatV4: rcvr <= arg]
  			inSmalltalk: [self booleanCheatV4: (objectMemory integerValueOf: rcvr) <= (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLessOrEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatV4: aBool].
  
  	messageSelector := self specialSelector: 4.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessThan (in category 'common selector sends') -----
  bytecodePrimLessThan
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheat: rcvr < arg]
  			inSmalltalk: [self booleanCheat: (objectMemory integerValueOf: rcvr) < (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLess: rcvr thanArg: arg.
  	self successful ifTrue: [^ self booleanCheat: aBool].
  
  	messageSelector := self specialSelector: 2.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessThanSistaV1 (in category 'common selector sends') -----
  bytecodePrimLessThanSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatSistaV1: rcvr < arg]
  			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) < (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLess: rcvr thanArg: arg.
  	self successful ifTrue: [^ self booleanCheatSistaV1: aBool].
  
  	messageSelector := self specialSelector: 2.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimLessThanV4 (in category 'common selector sends') -----
  bytecodePrimLessThanV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue:
- 	(self areIntegers: rcvr and: arg) ifTrue:
  		["The C code can avoid detagging since tagged integers are still signed.
  		 But this means the simulator must override to do detagging."
  		^self cCode: [self booleanCheatV4: rcvr < arg]
  			inSmalltalk: [self booleanCheatV4: (objectMemory integerValueOf: rcvr) < (objectMemory integerValueOf: arg)]].
  
  	self initPrimCall.
  	aBool := self primitiveFloatLess: rcvr thanArg: arg.
  	self successful ifTrue: [^ self booleanCheatV4: aBool].
  
  	messageSelector := self specialSelector: 2.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimMultiply (in category 'common selector sends') -----
  bytecodePrimMultiply
  	| rcvr arg result |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [rcvr := objectMemory integerValueOf: rcvr.
  				arg := objectMemory integerValueOf: arg.
  				result := rcvr * arg.
  				(arg = 0
  				 or: [(result // arg) = rcvr and: [objectMemory isIntegerValue: result]]) ifTrue:
  					[self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
  					 ^self fetchNextBytecode "success"]]
  		ifFalse: [self initPrimCall.
  				self externalizeIPandSP.
  				self primitiveFloatMultiply: rcvr byArg: arg.
  				self internalizeIPandSP.
  				self successful ifTrue: [^ self fetchNextBytecode "success"]].
  
  	messageSelector := self specialSelector: 8.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimNotEqual (in category 'common selector sends') -----
  bytecodePrimNotEqual
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheat: rcvr ~= arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheat: rcvr ~= arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheat: aBool not].
  
  	messageSelector := self specialSelector: 7.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimNotEqualSistaV1 (in category 'common selector sends') -----
  bytecodePrimNotEqualSistaV1
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr ~= arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr ~= arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatSistaV1: aBool not].
  
  	messageSelector := self specialSelector: 7.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimNotEqualV4 (in category 'common selector sends') -----
  bytecodePrimNotEqualV4
  	| rcvr arg aBool |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatV4: rcvr ~= arg].
- 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatV4: rcvr ~= arg].
  
  	self initPrimCall.
  	aBool := self primitiveFloatEqual: rcvr toArg: arg.
  	self successful ifTrue: [^self booleanCheatV4: aBool not].
  
  	messageSelector := self specialSelector: 7.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimSubtract (in category 'common selector sends') -----
  bytecodePrimSubtract
  	| rcvr arg result |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [result := (objectMemory integerValueOf: rcvr) - (objectMemory integerValueOf: arg).
  				(objectMemory isIntegerValue: result) ifTrue:
  					[self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
  					^self fetchNextBytecode "success"]]
  		ifFalse: [self initPrimCall.
  				self externalizeIPandSP.
  				self primitiveFloatSubtract: rcvr fromArg: arg.
  				self internalizeIPandSP.
  				self successful ifTrue: [^self fetchNextBytecode "success"]].
  
  	messageSelector := self specialSelector: 1.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>doPrimitiveDiv:by: (in category 'arithmetic primitive support') -----
  doPrimitiveDiv: rcvr by: arg
  	"Rounds negative results towards negative infinity, rather than zero."
  	| result posArg posRcvr integerRcvr integerArg |
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [integerRcvr := objectMemory integerValueOf: rcvr.
  				integerArg := objectMemory integerValueOf: arg.
  				self success: integerArg ~= 0]
  		ifFalse: [self primitiveFail].
  	self successful ifFalse: [^ 1 "fail"].
  
  	integerRcvr > 0
  		ifTrue: [integerArg > 0
  					ifTrue: [result := integerRcvr // integerArg]
  					ifFalse: ["round negative result toward negative infinity"
  							posArg := 0 - integerArg.
  							result := 0 - ((integerRcvr + (posArg - 1)) // posArg)]]
  		ifFalse: [posRcvr := 0 - integerRcvr.
  				integerArg > 0
  					ifTrue: ["round negative result toward negative infinity"
  							result := 0 - ((posRcvr + (integerArg - 1)) // integerArg)]
  					ifFalse: [posArg := 0 - integerArg.
  							result := posRcvr // posArg]].
  	self success: (objectMemory isIntegerValue: result).
  	^ result!

Item was changed:
  ----- Method: StackInterpreter>>doPrimitiveMod:by: (in category 'arithmetic primitive support') -----
  doPrimitiveMod: rcvr by: arg
  	| integerResult integerRcvr integerArg |
+ 	(objectMemory areIntegers: rcvr and: arg)
- 	(self areIntegers: rcvr and: arg)
  		ifTrue: [integerRcvr := objectMemory integerValueOf: rcvr.
  				integerArg := objectMemory integerValueOf: arg.
  				self success: integerArg ~= 0]
  		ifFalse: [self primitiveFail].
  	self successful ifFalse: [^ 1 "fail"].
  
  	integerResult := integerRcvr \\ integerArg.
  
  	"ensure that the result has the same sign as the integerArg"
  	integerArg < 0
  		ifTrue: [integerResult > 0
  			ifTrue: [integerResult := integerResult + integerArg]]
  		ifFalse: [integerResult < 0
  			ifTrue: [integerResult := integerResult + integerArg]].
  	self success: (objectMemory isIntegerValue: integerResult).
  	^ integerResult!

Item was changed:
  ----- Method: VMBasicConstants class>>mostBasicConstantSelectors (in category 'C translation') -----
  mostBasicConstantSelectors
  	"c.f. mostBasicConstantNames"
+ 	^#(	baseHeaderSize wordSize bytesPerOop shiftForWord
+ 		bytesPerWord "bytesPerWord isn't used, but kept for history"
+ 		minSmallInteger maxSmallInteger)!
- 	^#(baseHeaderSize wordSize bytesPerOop shiftForWord bytesPerWord "bytesPerWord isn't used, but kept for history")!

Item was changed:
  ----- Method: VMClass class>>writeVMHeaderTo:bytesPerWord: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord
  	"Generate the contents of interp.h on aStream.  Specific Interpreter subclasses
  	 override to add more stuff."
  	aStream
  		nextPutAll: '#define VM_PROXY_MAJOR '; print: self vmProxyMajorVersion; cr;
  		nextPutAll: '#define VM_PROXY_MINOR '; print: self vmProxyMinorVersion; cr;
  		cr;
  		nextPutAll: '#define SQ_VI_BYTES_PER_WORD '; print: bytesPerWord; cr;
  		cr.
  
  	"The most basic constants must be defined here, not in e.g. the plugin sources, so allow those
  	 other sources to be shared between different builds (Spur vs SqueakV3, 32-bit vs 64-bit, etc)"
  	VMBasicConstants mostBasicConstantNames asSet asArray sort do:
  		[:constName|
  		(VMBasicConstants classPool at: constName ifAbsent: []) ifNotNil:
  			[:const|
  			aStream nextPutAll: '#define '; nextPutAll: constName; space; print: const; cr]].
  	aStream cr.
  
  	((VMBasicConstants classPool associations select: [:a| a key beginsWith: 'PrimErr'])
  		asSortedCollection: [:a1 :a2| a1 value <= a2 value])
  		do: [:a|
  			aStream nextPutAll: '#define '; nextPutAll: a key; space; print: a value; cr].
+ 	aStream cr.
+ 
+ 	aStream
+ 		nextPutAll: '#define MinSmallInteger '; print: self objectMemoryClass minSmallInteger; cr;
+ 		nextPutAll: '#define MaxSmallInteger '; print: self objectMemoryClass maxSmallInteger; cr;
+ 		cr.!
- 	aStream cr!



More information about the Vm-dev mailing list