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

commits at source.squeak.org commits at source.squeak.org
Sat Nov 22 21:13:11 UTC 2014


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

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

Name: VMMaker.oscog-eem.953
Author: eem
Time: 22 November 2014, 1:10:42.674 pm
UUID: 62e5308c-b39a-464e-a2d5-ce7b6573d462
Ancestors: VMMaker.oscog-eem.952

Implement SmallFloat primitives.
Fix code generator to allow <option: #Spur64BitMemoryManager>
Implement exponentOfSmallFloat:.
Correctly define smallFloatExponentOffset.
Fix smallFloatObjectOf: for simulation.
Avoid cCode: '... modf(...' in two prims using self mod: f: instead.

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

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
  	"Answer whether a method shoud be translated.  Process optional methods by
  	 interpreting the argument to the option: pragma as either a Cogit class name
  	 or a class variable name or a variable name in VMBasicConstants.  Exclude
  	 methods with the doNotGenerate pragma."
  	| pragmas |
  	"where is pragmasAt: ??"
  	(pragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:]) notEmpty ifTrue:
  		[pragmas do:
  			[:pragma| | key |
  			 key := pragma argumentAt: 1.
  			 "If the option is the name of a subclass of Cogit, include it if it inherits from the Cogit class."
  			 (Smalltalk classNamed: key) ifNotNil:
  				[:optionClass|
  				 aClass cogitClass ifNotNil:
  					[:cogitClass|
+ 					 (optionClass includesBehavior: Cogit) ifTrue:
+ 						[^cogitClass includesBehavior: optionClass]].
+ 				 aClass objectMemoryClass ifNotNil:
+ 					[:objectMemoryClass|
+ 					 ((optionClass includesBehavior: ObjectMemory)
+ 					   or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
+ 						[^objectMemoryClass includesBehavior: optionClass]]].
- 					 (Cogit withAllSubclasses anySatisfy: [:c| c = cogitClass]) ifTrue:
- 						[^cogitClass includesBehavior: optionClass]]].
  			 "Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
  			 {aClass initializationOptions.
  			   aClass.
  			   VMBasicConstants.
  			   aClass interpreterClass.
  			   aClass objectMemoryClass} do:
  				[:scopeOrNil|
  				 scopeOrNil ifNotNil:
  					[:scope|
  					 (scope bindingOf: key) ifNotNil:
  						[:binding|
  						binding value ~~ false ifTrue: [^true]]]]].
  		^false].
  	^(aClass >> selector pragmaAt: #doNotGenerate) isNil!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFractionalPart (in category 'arithmetic float primitives') -----
  primitiveFractionalPart
  	| rcvr frac trunc |
  	<var: #rcvr type: #double>
  	<var: #frac type: #double>
  	<var: #trunc type: #double>
  	rcvr := self popFloat.
  	self successful
+ 		ifTrue: [frac := self cCode: [self mod: rcvr f: (self addressOf: trunc)]
+ 							inSmalltalk: [rcvr fractionPart].
- 		ifTrue: [self cCode: 'frac = modf(rcvr, &trunc)' inSmalltalk: [frac := rcvr fractionPart].
  				self pushFloat: frac]
  		ifFalse: [self unPop: 1]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatAdd (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatAdd
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushFloat: rcvr + arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatArctan (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatArctan
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr |
+ 	<var: #rcvr type: #double>
+ 	rcvr := objectMemory smallFloatValueOf: self stackTop.
+ 	self pop: 1
+ 		thenPushFloat: (self cCode: [rcvr atan]
+ 							inSmalltalk: [rcvr = rcvr
+ 											ifTrue: [rcvr arcTan]
+ 											ifFalse: [Float nan]])!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatDivide (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatDivide
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushFloat: rcvr / arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatEqual (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: rcvr = arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatExp (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatExp
+ 	"Computes E raised to the receiver power.
+ 	 Since SmallFloats cannot represent NaNs there's no need to special case."
+ 	<option: #Spur64BitMemoryManager>
+ 
+ 	self pop: 1 thenPushFloat: (objectMemory smallFloatValueOf: self stackTop) exp!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatExponent (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatExponent
+ 	"Answer the exponent part of this float."
+ 	<option: #Spur64BitMemoryManager>
+ 
+ 	self pop: 1 thenPushInteger: (objectMemory exponentOfSmallFloat: self stackTop) - 1!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatFractionalPart (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatFractionalPart
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr frac trunc |
+ 	<var: #rcvr type: #double>
+ 	<var: #frac type: #double>
+ 	<var: #trunc type: #double>
+ 	rcvr := objectMemory smallFloatValueOf: self stackTop.
+ 	frac := self cCode: [self mod: rcvr f: (self addressOf: trunc)]
+ 				inSmalltalk: [rcvr fractionPart].
+ 	self pop: 1 thenPushFloat: frac!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterOrEqual (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatGreaterOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: rcvr >= arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterThan (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatGreaterThan
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: rcvr > arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessOrEqual (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatLessOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: rcvr <= arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessThan (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatLessThan
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: rcvr < arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatLogN (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatLogN
+ 	"Natural log."
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr |
+ 	<var: #rcvr type: #double>
+ 	rcvr := objectMemory smallFloatValueOf: self stackTop.
+ 	self pop: 1
+ 		thenPushFloat: (self cCode: [rcvr log]
+ 							inSmalltalk: [rcvr = rcvr
+ 											ifTrue: [rcvr ln]
+ 											ifFalse: [Float nan]])!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatMultiply (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatMultiply
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushFloat: rcvr * arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatNotEqual (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatNotEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushBool: (rcvr = arg) not]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatSine (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatSine
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr |
+ 	<var: #rcvr type: #double>
+ 	rcvr := objectMemory smallFloatValueOf: self stackTop.
+ 	self pop: 1
+ 		thenPushFloat: (self cCode: [rcvr sin]
+ 							inSmalltalk: [rcvr = rcvr
+ 											ifTrue: [rcvr sin]
+ 											ifFalse: [Float nan]])!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatSquareRoot (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatSquareRoot
+ 	<option: #Spur64BitMemoryManager>
+ 
+ 	self pop: 1 thenPushFloat: (objectMemory smallFloatValueOf: self stackTop) sqrt!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatSubtract (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatSubtract
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	<var: #arg type: #double>
+ 
+ 	rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 	arg := self loadFloatOrIntFrom: self stackTop.
+ 	self successful ifTrue:
+ 		[self pop: 2 thenPushFloat: rcvr - arg]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatTimesTwoPower (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatTimesTwoPower
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr arg |
+ 	<var: #rcvr type: #double>
+ 	arg := self stackTop.
+ 	(objectMemory isIntegerObject: arg)
+ 		ifTrue:
+ 			[rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
+ 			 arg := objectMemory integerValueOf: arg.
+ 			 self pop: 1
+ 				thenPushFloat: (self cCode: [self ld: rcvr exp: arg]
+ 									inSmalltalk: [rcvr timesTwoPower: arg])]
+ 		ifFalse:
+ 			[self primitiveFail]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSmallFloatTruncated (in category 'arithmetic float primitives') -----
+ primitiveSmallFloatTruncated
+ 	<option: #Spur64BitMemoryManager>
+ 	| rcvr trunc |
+ 	<var: #rcvr type: #double>
+ 	<var: #trunc type: #double>
+ 	rcvr := self smallFloatValueOf: self stackTop.
+ 	self cCode: [self mod: rcvr f: (self addressOf: trunc)]
+ 		inSmalltalk: [trunc := rcvr truncated].
+ 	(trunc between: SmallInteger minVal asFloat and: SmallInteger maxVal asFloat)
+ 		ifTrue: [self pop: 1 thenPushInteger: trunc asInteger]
+ 		ifFalse: [self primitiveFail]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveTruncated (in category 'arithmetic float primitives') -----
  primitiveTruncated 
+ 	| rcvr trunc |
- 	| rcvr frac trunc |
  	<var: #rcvr type: #double>
- 	<var: #frac type: #double>
  	<var: #trunc type: #double>
  	rcvr := self popFloat.
  	self successful ifTrue:
+ 		[self cCode: [self mod: rcvr f: (self addressOf: trunc)]
- 		[self cCode: 'frac = modf(rcvr, &trunc)'
  			inSmalltalk: [trunc := rcvr truncated].
+ 		self success: (trunc between: SmallInteger minVal asFloat and: SmallInteger maxVal asFloat)].
- 		self flag: #Dan.		"The ranges are INCORRECT if SmallIntegers are wider than 31 bits."
- 		self cCode: 'success((-1073741824.0 <= trunc) && (trunc <= 1073741823.0))'
- 			inSmalltalk: [self success: (trunc between: SmallInteger minVal and: SmallInteger maxVal)]].
  	self successful
+ 		ifTrue: [self pushInteger: trunc asInteger]
- 		ifTrue: [self cCode: 'pushInteger((sqInt) trunc)' inSmalltalk: [self pushInteger: trunc]]
  		ifFalse: [self unPop: 1]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>exponentOfSmallFloat: (in category 'interpreter access') -----
+ exponentOfSmallFloat: oop
+ 	"Answer the exponent of the argument, a SmallFloat.
+ 	 See section 61-bit Immediate Floats in the SpurMemoryManager class comment.
+ 				msb                                              lsb 
+ 				[8expsubset][52mantissa][1s][3tags]"
+ 	| exp |
+ 	self assert: (oop bitAnd: self tagMask) = self smallFloatTag.
+ 	^oop <= 15
+ 		ifTrue: [0]
+ 		ifFalse:
+ 			[exp := oop >> (self numTagBits + self smallFloatMantissaBits + 1).
+ 			 exp + self smallFloatExponentOffset - 1022]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>smallFloatExponentOffset (in category 'interpreter access') -----
  smallFloatExponentOffset
+ 	"896 is 1023 - 127, where 1023 is the mid-point of the 11-bit double precision exponent range,
+ 	 and 127 is the mid-point of the 8-bit SmallDouble exponent range."
+ 	^896!
- 	^128!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>smallFloatObjectOf: (in category 'interpreter access') -----
  smallFloatObjectOf: aFloat
  	"Encode the argument, aFloat in the SmallFloat range, as a tagged small float.
  	 See section 61-bit Immediate Floats in the SpurMemoryManager class comment.
  
+ 	 Encode:				[1s][     11 exponent     ][52mantissa] 
- 	 Encode:					[1s][     11 exponent     ][52mantissa] 
  	 rot sign:				[     11 exponent     ][52mantissa][1s] 
  	 sub exponent offset:	[ 000 ][8expsubset][52 mantissa][1s] 
  	 shift:					[8expsubset][52 mantissa][1s][ 000 ] 
  	 or/add tags:			[8expsubset][52mantissa][1s][3tags]"
  	<inline: true>
  	<var: #aFloat type: #double>
  	| rawFloat rot |
+ 	self assert: (self isSmallFloatValue: aFloat).
+ 	rawFloat := self cCode: [(self cCoerce: (self addressOf: aFloat) to: 'sqLong *') at: 0]
- 	rawFloat := self
- 					cCode:
- 						[(self cCoerce: (self addressOf: aFloat) to: 'sqLong *') at: 0]
  					inSmalltalk: [(aFloat at: 1) << 32 + (aFloat at: 2)].
  	rot := self rotateLeft: rawFloat.
  	rot > 1 ifTrue:
  		[rot := rot - (self smallFloatExponentOffset << (self smallFloatMantissaBits + 1)).
  		 self assert: rot > 0].
+ 	^self cCode: [rot << self numTagBits + self smallFloatTag]
+ 		inSmalltalk: [((rot << self numTagBits) bitAnd: 16rFFFFFFFFFFFFFFFF) + self smallFloatTag]!
- 	^rot << self numTagBits + self smallFloatTag!



More information about the Vm-dev mailing list