[Vm-dev] VM Maker: VMMaker-dtl.287.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 2 14:34:40 UTC 2012


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.287.mcz

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

Name: VMMaker-dtl.287
Author: dtl
Time: 2 September 2012, 10:33:04.159 am
UUID: 486209ad-7082-4e05-84a9-f37c4c6ba622
Ancestors: VMMaker-dtl.286

VMMaker 4.10.2

Remove unnecessary type declarations added in the last update (4.10.1).

Rationale: Do not declare oop as usqInt unless there is a need to do so. Arguably, all oop values should be unsigned throughout the VM, and this should be declared as a specific oop data type independent of sqInt and usqInt. But this is a more general issue throughout the VM, meanwhile the explicit declarations of oop values as usqInt have no practical effect.

Remove some unneeded <inline: false> declarations.

=============== Diff against VMMaker-dtl.286 ===============

Item was changed:
  ----- Method: InterpreterPrimitives>>isNegativeIntegerValueOf: (in category 'primitive support') -----
  isNegativeIntegerValueOf: oop
+ 	"Answer true if integer object is negative.
- 	"Answer 1 if integer object is negative, 0 otherwise.
  	Fail if object pointed by oop i not an integer."
  	| ok smallInt |
+ 
- 	<inline: false>
- 	<returnTypeC: #usqInt>
- 	<var: #smallInt type: #sqInt>
- 	
  	(objectMemory isIntegerObject: oop)
  		ifTrue:
  			[smallInt := objectMemory integerValueOf: oop.
  			^smallInt < 0].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok ifTrue: [^false].
  		
  	ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  	ok ifTrue: [^true].
  	self primitiveFail.
  	^false!

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 |
- 	<inline: false>
  	<var: 'magnitude' type: 'usqLong'>
- 	<var: 'isNegative' type: 'usqInt'>
  	<var: 'highWord' type: 'usqInt'>
- 	<var: 'isSmall' type: 'usqInt'>
- 	<var: 'smallVal' type: 'sqInt'>
  
  	isSmall := isNegative
  		ifTrue: [magnitude <= 16r40000000]
  		ifFalse: [magnitude < 16r40000000].
  	isSmall
  		ifTrue:
  			[smallVal := self cCoerce: magnitude to: #sqInt.
  			isNegative	ifTrue: [smallVal := 0 - smallVal].
  			^self integerObjectOf: smallVal].
  	isNegative
  		ifTrue:[	largeClass := self classLargeNegativeInteger]
  		ifFalse:[	largeClass := self classLargePositiveInteger].
  	highWord := self cCode: 'magnitude >> 32'. "shift is coerced to usqInt otherwise"
  	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 := self instantiateClass: largeClass indexableSize:  sz.
  	0 to: sz-1 do: [:i |
  		intValue := self cCode: '(magnitude >> (i * 8)) & 255'.
  		self storeByte: i ofObject: newLargeInteger withValue: intValue].
  	^ newLargeInteger!

Item was changed:
  ----- Method: InterpreterPrimitives>>magnitude64BitValueOf: (in category 'primitive support') -----
  magnitude64BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or a eight-byte LargeInteger."
  	| sz value ok smallIntValue |
- 	<inline: false>
  	<returnTypeC: #usqLong>
  	<var: #value type: #usqLong>
+ 
- 	<var: #smallIntValue type: #sqInt>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[smallIntValue := (objectMemory integerValueOf: oop).
  		smallIntValue < 0 ifTrue: [smallIntValue := 0 - smallIntValue].
  		^self cCoerce: smallIntValue to: #usqLong].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifFalse:
  			[ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse: [^self primitiveFail]].
  	sz := objectMemory lengthOf: oop.
  	sz > (self sizeof: #sqLong asSymbol) ifTrue:
  		[^self primitiveFail].
  
  	value := 0.
  	0 to: sz - 1 do: [:i |
  		value := value + ((self cCoerce: (objectMemory fetchByte: i ofObject: oop) to: #sqLong) <<  (i*8))].
  	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveAddLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveAddLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| a b result oopResult aIsNegative bIsNegative resultIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
- 	<var: 'resultIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	self successful ifFalse:[^nil].
  	(aIsNegative = bIsNegative)
  		ifTrue:
  			["Protect against overflow"
  			a > (16rFFFFFFFFFFFFFFFF - b) ifTrue: [self primitiveFail. ^nil].
  			result := a + b.
  			resultIsNegative := aIsNegative]
  		ifFalse:
  			[(a >= b)
  				ifTrue:
  					[result := a - b.
  					resultIsNegative := aIsNegative]
  				ifFalse:
  					[result := b - a.
  					resultIsNegative := bIsNegative]].
  	oopResult := self magnitude64BitIntegerFor: result neg: resultIsNegative.
  	self successful ifTrue:[self pop: 2 thenPush: oopResult].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitShiftLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveBitShiftLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| a shift result oopResult aIsNegative oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
- 	<var: 'shift' type: 'sqInt'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
  
  	shift := self stackIntegerValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	a := self magnitude64BitValueOf: oopRcvr.
  	self successful ifFalse:[^nil].
  	(shift >= 0)
  		ifTrue:
  			["Protect against overflow"
  			result := 16rFFFFFFFFFFFFFFFF. "This is to avoid undue (usqInt) cast"
  			(shift >= 64 or: [a > (result >> shift)]) ifTrue: [self primitiveFail. ^nil].
  			result := a << shift]
  		ifFalse:
  			[shift := 0 - shift.
  			shift >= 64
  				ifTrue: [result := 0]
  				ifFalse: [result := a >> shift].
  			"Fake 2 complement for negative values"
  			(aIsNegative and: [result << shift ~= a]) ifTrue: [result := result + 1]].
  	oopResult := self magnitude64BitIntegerFor: result neg: aIsNegative.
  	self successful ifTrue:[self pop: 2 thenPush: oopResult].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveDivLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveDivLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| result oopResult a aIsNegative b bIsNegative oopArg oopRcvr rem |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
  	<var: 'rem' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	b = 0 ifTrue:[self primitiveFail].
  	self successful ifFalse:[^nil].
  
  	result := a // b.
  	
  	a = 0
  		ifFalse: [bIsNegative = aIsNegative
  			ifFalse:
  				["Round toward negative infinity"
  				rem := a \\ b.
  				rem = 0 ifFalse:
  					["This can not overflow, because b > 1, otherwise rem = 0"
  					result := result + 1]]].
  
  	oopResult := self magnitude64BitIntegerFor: result neg: bIsNegative ~= aIsNegative.
  	self successful ifTrue: [self pop: 2 thenPush: oopResult].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveDivideLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveDivideLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| a b result oopResult aIsNegative bIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	self successful ifFalse:[^nil].
  	
  	"check for exact division"
  	(b ~= 0 and:[a \\ b = 0]) ifFalse:[self primitiveFail. ^nil].
  
  	result := a // b.
  	oopResult := self magnitude64BitIntegerFor: result neg: aIsNegative ~= bIsNegative.
  
  	self successful ifTrue:[self pop: 2 thenPush: oopResult].
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveModLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveModLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| result oopResult a aIsNegative b bIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	b = 0 ifTrue:[self primitiveFail].
  	self successful ifFalse:[^nil].
  
  	result := a \\ b.
  
  	"Handle remainder of same sign as argument"
  	result = 0
  		ifFalse: [bIsNegative = aIsNegative
  			ifFalse: [result := b - result]].
  
  	oopResult := self magnitude64BitIntegerFor: result neg: bIsNegative.
  	self successful ifTrue: [self pop: 2 thenPush: oopResult].
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveMultiplyLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveMultiplyLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| a b result oopResult aIsNegative bIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	self successful ifFalse:[^nil].
  	
  	"check for overflow"
  	(a > 1 and: [b > 1 and: [a > (16rFFFFFFFFFFFFFFFF / b)]])
  		ifTrue: [self primitiveFail. ^nil].
  
  	result := a * b.
  	oopResult := self magnitude64BitIntegerFor: result neg: aIsNegative ~= bIsNegative.
  
  	self successful ifTrue:[self pop: 2 thenPush: oopResult].
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveQuoLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveQuoLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| result oopResult a aIsNegative b bIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	b = 0 ifTrue:[self primitiveFail].
  	self successful ifFalse:[^nil].
  
  	result := a // b.
  
  	oopResult := self magnitude64BitIntegerFor: result neg: bIsNegative ~= aIsNegative.
  	self successful ifTrue: [self pop: 2 thenPush: oopResult].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveRemLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveRemLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| result oopResult a aIsNegative b bIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	b = 0 ifTrue:[self primitiveFail].
  	self successful ifFalse:[^nil].
  
  	result := a \\ b.
  
  	oopResult := self magnitude64BitIntegerFor: result neg: aIsNegative ~= bIsNegative.
  	self successful ifTrue: [self pop: 2 thenPush: oopResult].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSubtractLargeIntegers (in category 'arithmetic largeint primitives') -----
  primitiveSubtractLargeIntegers
  	"Primitive arithmetic operations for large integers in 64 bit range"
  	| a b result oopResult aIsNegative bIsNegative resultIsNegative oopArg oopRcvr |
  	<export: true>
  	<var: 'a' type: 'usqLong'>
  	<var: 'b' type: 'usqLong'>
  	<var: 'result' type: 'usqLong'>
- 	<var: 'oopArg' type: 'usqInt'>
- 	<var: 'oopRcvr' type: 'usqInt'>
- 	<var: 'oopResult' type: 'usqInt'>
- 	<var: 'aIsNegative' type: 'usqInt'>
- 	<var: 'bIsNegative' type: 'usqInt'>
- 	<var: 'resultIsNegative' type: 'usqInt'>
  
  	oopArg := self stackValue: 0.
  	oopRcvr := self stackValue: 1.
  	aIsNegative := self isNegativeIntegerValueOf: oopRcvr.
  	bIsNegative := self isNegativeIntegerValueOf: oopArg.
  	a := self magnitude64BitValueOf: oopRcvr.
  	b := self magnitude64BitValueOf: oopArg.
  	self successful ifFalse:[^nil].
  	(aIsNegative ~= bIsNegative)
  		ifTrue:
  			["Protect against overflow"
  			a > (16rFFFFFFFFFFFFFFFF - b) ifTrue: [self primitiveFail. ^nil].
  			result := a + b.
  			resultIsNegative := aIsNegative]
  		ifFalse:
  			[(a >= b)
  				ifTrue:
  					[result := a - b.
  					resultIsNegative := aIsNegative]
  				ifFalse:
  					[result := b - a.
  					resultIsNegative := aIsNegative not]].
  	oopResult := self magnitude64BitIntegerFor: result neg: resultIsNegative.
  	self successful ifTrue:[self pop: 2 thenPush: oopResult].
  !

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.10.2'!
- 	^'4.10.1'!



More information about the Vm-dev mailing list