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

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


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

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

Name: VMMaker.oscog-eem.1056
Author: eem
Time: 11 February 2015, 6:06:30.048 pm
UUID: 3069334b-0e1a-4609-840d-f85302692f97
Ancestors: VMMaker.oscog-eem.1055

Range-check the three float timesTwoPower:
implementations to ensure that the argument to
ldexp does not exceed int range.

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

Item was added:
+ ----- Method: FloatMathPlugin>>isFinite: (in category 'float primitives') -----
+ isFinite: aDouble
+ 	<var: #aDouble type: #double>
+ 	<inline: true>
+ 	^aDouble - aDouble = 0.0!

Item was changed:
  ----- Method: FloatMathPlugin>>primitiveTimesTwoPower (in category 'float primitives') -----
  primitiveTimesTwoPower
  	"Computes E raised to the receiver power."
+ 	| rcvr arg twiceMaxExponent result |
- 	| rcvr arg result |
  	<export: true>
+ 	<var: #rcvr type: #double>
+ 	<var: #result type: #double>
- 	<var: #rcvr type: 'double'>
- 	<var: #result type: 'double'>
  	arg := interpreterProxy stackIntegerValue: 0.
  	rcvr := interpreterProxy stackFloatValue: 1.
+ 	interpreterProxy failed ifTrue:
+ 		[^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!
- 	(interpreterProxy failed) ifTrue:[^nil].
- 	result := self cCode: '__ieee754_ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg].
- 	(self isnan: result) ifTrue:[^interpreterProxy primitiveFail].
- 	interpreterProxy pop: interpreterProxy methodArgumentCount + 1.
- 	interpreterProxy pushFloat: result.!

Item was added:
+ ----- Method: InterpreterPrimitives>>floatExponentBits (in category 'primitive support') -----
+ floatExponentBits
+ 	"Answer the number of bits in the double-precision exponent.  This is an 11-bit field."
+ 	^11!

Item was added:
+ ----- Method: InterpreterPrimitives>>isFinite: (in category 'primitive support') -----
+ isFinite: aDouble
+ 	<var: #aDouble type: #double>
+ 	<inline: true>
+ 	^aDouble - aDouble = 0.0!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSmallFloatTimesTwoPower (in category 'arithmetic float primitives') -----
  primitiveSmallFloatTimesTwoPower
  	<option: #Spur64BitMemoryManager>
+ 	| rcvr result arg twiceMaxExponent |
- 	| rcvr arg |
  	<var: #rcvr type: #double>
+ 	<var: #result type: #double>
  	arg := self stackTop.
+ 	(objectMemory isIntegerObject: arg) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	"N.B. SmallFloats are finite.  NaN and Infinity overflow into boxed floats."
+ 	rcvr = 0.0
- 	(objectMemory isIntegerObject: arg)
  		ifTrue:
+ 			[result := rcvr]
- 			[rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
- 			 arg := objectMemory integerValueOf: arg.
- 			 self pop: 2
- 				thenPushFloat: (self cCode: [self ld: rcvr exp: arg]
- 									inSmalltalk: [rcvr timesTwoPower: arg])]
  		ifFalse:
+ 			[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!
- 			[self primitiveFail]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveTimesTwoPower (in category 'arithmetic float primitives') -----
  primitiveTimesTwoPower
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr result arg twiceMaxExponent |
- 	| rcvr arg |
  	<var: #rcvr type: #double>
+ 	<var: #result type: #double>
+ 	arg := self stackTop.
+ 	(objectMemory isIntegerObject: arg) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	rcvr := objectMemory floatValueOf: (self stackValue: 1).
+ 	((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!
- 	arg := self popInteger.
- 	rcvr := self popFloat.
- 	self successful
- 		ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
- 		ifFalse: [ self unPop: 2 ]!



More information about the Vm-dev mailing list