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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 12 18:08:09 UTC 2015


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

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

Name: VMMaker.oscog-eem.1058
Author: eem
Time: 12 February 2015, 10:06:39.955 am
UUID: fdd2ee43-600b-4068-9956-dc6d59e05044
Ancestors: VMMaker.oscog-eem.1057

Revisit primitiveTimesTwoPower.  Avoid complications
in the 32-bit versions.  Clip the argument in the 64-bit
versions and avoid the compiler warning with a cast.

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

Item was changed:
  ----- Method: FloatMathPlugin>>primitiveTimesTwoPower (in category 'float primitives') -----
  primitiveTimesTwoPower
+ 	"Multiply the receiver by the power of the argument."
+ 	| rcvr arg result |
- 	"Computes E raised to the receiver power."
- 	| rcvr arg twiceMaxExponent result |
  	<export: true>
  	<var: #rcvr type: #double>
  	<var: #result type: #double>
  	arg := interpreterProxy stackIntegerValue: 0.
  	rcvr := interpreterProxy stackFloatValue: 1.
  	interpreterProxy failed ifTrue:
  		[^nil].
+ 	interpreterProxy bytesPerOop > 4 ifTrue:
+ 		[| twiceMaxExponent | "clip arg to at most int range; ldexp's last arg is of type int"
+ 		 twiceMaxExponent := 2 * (1 << self floatExponentBits).
+ 	 	 arg < twiceMaxExponent negated
+ 			ifTrue: [arg := twiceMaxExponent negated]
+ 			ifFalse: [arg > twiceMaxExponent ifTrue:
+ 						[arg := twiceMaxExponent]]].
+ 	result := self cCode: '__ieee754_ldexp(rcvr, (int)arg)'
+ 					inSmalltalk: [rcvr timesTwoPower: arg].
+ 	(self isnan: result) ifFalse:
+ 		[interpreterProxy methodReturnValue: (interpreterProxy floatObjectOf: result)].
+ 	^nil!
- 	((self isFinite: rcvr) and: [rcvr ~= 0.0])
- 		ifFalse:
- 			[result := rcvr]
- 		ifTrue:
- 			[twiceMaxExponent := 2 * (1 << 11).
- 			 arg < twiceMaxExponent negated
- 				ifTrue:
- 					[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
- 				ifFalse:
- 					[arg > twiceMaxExponent
- 						ifTrue:
- 							[result := rcvr < 0.0 ifTrue: [-1.0e200 / 1.0e-200] ifFalse: [1.0e200 / 1.0e-200]]
- 						ifFalse:
- 							[result := self cCode: '__ieee754_ldexp(rcvr, arg)'
- 											inSmalltalk: [rcvr timesTwoPower: arg]]]].
- 	(self isnan: result) ifTrue:
- 		[^interpreterProxy primitiveFail].
- 	interpreterProxy
- 		pop: interpreterProxy methodArgumentCount + 1;
- 		pushFloat: result!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSmallFloatTimesTwoPower (in category 'arithmetic float primitives') -----
  primitiveSmallFloatTimesTwoPower
+ 	"Multiply the receiver by the power of the argument."
  	<option: #Spur64BitMemoryManager>
  	| rcvr result arg twiceMaxExponent |
- 	<var: #rcvr type: #double>
- 	<var: #result type: #double>
  	arg := self stackTop.
  	(objectMemory isIntegerObject: arg) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	rcvr := self stackValue: 1.
+ 	"N.B. SmallFloats are finite.  NaN and Infinity overflow into boxed floats.
+ 	 This is doing range checking work that is done in ldexp, but we include
+ 	 it explicitly to exemplify bit manipulation of SmallFloats."
+ 	(objectMemory isSmallFloatZero: rcvr)
- 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
- 	"N.B. SmallFloats are finite.  NaN and Infinity overflow into boxed floats."
- 	rcvr = 0.0
  		ifTrue:
  			[result := rcvr]
  		ifFalse:
  			[arg := objectMemory integerValueOf: arg.
  			 twiceMaxExponent := 2 * (1 << self floatExponentBits).
  			 arg < twiceMaxExponent negated
  				ifTrue:
+ 					[result := objectMemory mapSignedSmallFloatToSignedSmallFloatZero: rcvr]
- 					[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
  				ifFalse:
+ 					["clip arg to at most int range; ldexp's last arg is of type int"
+ 					 arg > twiceMaxExponent ifTrue: [arg := twiceMaxExponent].
+ 					 result := objectMemory floatObjectOf: (self cCode: [self ld: (objectMemory smallFloatValueOf: rcvr)
+ 																				exp: (self cCoerceSimple: arg to: #int)]
+ 																inSmalltalk: [(objectMemory smallFloatValueOf: rcvr) timesTwoPower: arg])]].
+ 	self pop: 2 thenPush: result!
- 					[arg > twiceMaxExponent
- 						ifTrue:
- 							[result := rcvr < 0.0 ifTrue: [-1.0e200 / 1.0e-200] ifFalse: [1.0e200 / 1.0e-200]]
- 						ifFalse:
- 							[result := self cCode: [self ld: rcvr exp: arg]
- 											inSmalltalk: [rcvr timesTwoPower: arg]]]].
- 	self pop: 2 thenPushFloat: result!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveTimesTwoPower (in category 'arithmetic float primitives') -----
  primitiveTimesTwoPower
+ 	"Multiply the receiver by the power of the argument."
  	<option: #Spur64BitMemoryManager>
+ 	| rcvr result arg |
- 	| rcvr result arg twiceMaxExponent |
  	<var: #rcvr type: #double>
  	<var: #result type: #double>
  	arg := self stackTop.
  	(objectMemory isIntegerObject: arg) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	arg := objectMemory integerValueOf: arg.
+ 	objectMemory bytesPerOop > 4 ifTrue:
+ 		[| twiceMaxExponent | "clip arg to at most int range; ldexp's last arg is of type int"
+ 		 twiceMaxExponent := 2 * (1 << self floatExponentBits).
+ 	 	 arg < twiceMaxExponent negated
+ 			ifTrue: [arg := twiceMaxExponent negated]
+ 			ifFalse: [arg > twiceMaxExponent ifTrue:
+ 						[arg := twiceMaxExponent]]].
  	rcvr := objectMemory floatValueOf: (self stackValue: 1).
+ 	result := self cCode: [self ld: rcvr exp: (self cCoerceSimple: arg to: #int)]
+ 					inSmalltalk: [rcvr timesTwoPower: arg].
- 	((self isFinite: rcvr) and: [rcvr ~= 0])
- 		ifFalse:
- 			[result := rcvr]
- 		ifTrue:
- 			[arg := objectMemory integerValueOf: arg.
- 			 twiceMaxExponent := 2 * (1 << self floatExponentBits).
- 			 arg < twiceMaxExponent negated
- 				ifTrue:
- 					[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
- 				ifFalse:
- 					[arg > twiceMaxExponent
- 						ifTrue:
- 							[result := rcvr < 0.0 ifTrue: [-1.0e200 / 1.0e-200] ifFalse: [1.0e200 / 1.0e-200]]
- 						ifFalse:
- 							[result := self cCode: [self ld: rcvr exp: arg]
- 											inSmalltalk: [rcvr timesTwoPower: arg]]]].
  	self pop: 2 thenPushFloat: result!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isNegativeSmallFloat: (in category 'interpreter access') -----
+ isNegativeSmallFloat: aSmallFloat
+ 	<inline: true>
+ 	self assert: (self isImmediateFloat: aSmallFloat).
+ 	^aSmallFloat anyMask: self smallFloatSignBit!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isSmallFloatZero: (in category 'interpreter access') -----
+ isSmallFloatZero: aSmallFloat
+ 	<inline: true>
+ 	self assert: (self isImmediateFloat: aSmallFloat).
+ 	^aSmallFloat asUnsignedInteger <= self negativeSmallFloatZero!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>mapSignedSmallFloatToSignedSmallFloatZero: (in category 'interpreter access') -----
+ mapSignedSmallFloatToSignedSmallFloatZero: aSmallFloat
+ 	<inline: true>
+ 	self assert: (self isImmediateFloat: aSmallFloat).
+ 	^aSmallFloat bitAnd: self smallFloatSignBit + self tagMask!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>negativeSmallFloatZero (in category 'interpreter access') -----
+ negativeSmallFloatZero
+ 	<inline: true>
+ 	^self smallFloatSignBit + self smallFloatTag!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>positiveSmallFloatZero (in category 'interpreter access') -----
+ positiveSmallFloatZero
+ 	<inline: true>
+ 	^self smallFloatTag!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>rotatedFloatBitsOf: (in category 'interpreter access') -----
  rotatedFloatBitsOf: oop
  	"Answer the signed, but unadjusted value of a SmallFloat64, suitable for use as a hash.
  	 Keeping the exponent unadjusted keeps the value in the SmallInteger range.
  	 See section 61-bit Immediate Floats in the SpurMemoryManager class comment.
  							msb                                             lsb 
  	 Decode:				[8expsubset][52mantissa][1s][3tags] 
  	 shift away tags & sign:	[   0000   ][8expsubset][52mantissa]
  	 add sign:				[    ssss   ][8expsubset][52mantissa]"
  	self assert: (self isImmediateFloat: oop).
  	^oop asUnsignedInteger >> (self numTagBits + 1)
+ 	 + ((oop anyMask: self smallFloatSignBit)
- 	 + ((oop anyMask: 1 << self numTagBits)
  		ifTrue: [-1 << (64 - self numTagBits - 1)]
  		ifFalse: [0])!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>smallFloatSignBit (in category 'interpreter access') -----
+ smallFloatSignBit
+ 	<inline: true>
+ 	^1 << self numTagBits!



More information about the Vm-dev mailing list