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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 25 21:16:33 UTC 2015


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

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

Name: VMMaker.oscog-eem.1081
Author: eem
Time: 25 February 2015, 1:15:04.185 pm
UUID: 4cd33ad1-8b0f-4537-bf5f-7a4a25a1a2f9
Ancestors: VMMaker.oscog-eem.1080

General:
Take advantage of endianness for simpler large
integer initialization.

Slang:
Fix inlining of (u)sqLong expressions bound to
untyped formals; since the system expects untyped
formals to be of type #sqInt the expr must be cast
to #sqInt.

Put node:typeCompatibleWith:inliningInto:in: in
CCodeGenerator, not TMethod.

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

Item was added:
+ ----- Method: CCodeGenerator>>node:typeCompatibleWith:inliningInto:in: (in category 'inlining') -----
+ node: exprNode typeCompatibleWith: argName inliningInto: inlineSelector in: aTMethod
+ 	"Answer either exprNode or, if required, a cast of exprNode to the type of argName.
+ 	 The cast is required if
+ 		- argName is typed and exprNode is untyped
+ 		- argName is untyped and exprNode is an arithmetic type of size > #sqInt
+ 		- both argName and exprNode are typed but they are incompatible"
+ 	| formalType actualType |
+ 	formalType := aTMethod typeFor: argName in: self.
+ 	actualType := self typeFor: exprNode in: aTMethod.
+ 	^((exprNode isSend or: [exprNode isVariable])
+ 	   and: [(formalType notNil and: [actualType isNil])
+ 			or: [(formalType isNil and: [actualType notNil and: [(self isIntegralCType: actualType) and: [(self sizeOfIntegralCType: actualType) > (self sizeOfIntegralCType: #sqInt)]]])
+ 			or: [(self variableOfType: formalType acceptsValue: exprNode ofType: actualType) not]]])
+ 		ifTrue: [self nodeToCast: exprNode to: (formalType ifNil: [#sqInt])]
+ 		ifFalse:
+ 			[((exprNode isSend or: [exprNode isVariable])
+ 			  and: [(self
+ 					variableOfType: (self typeFor: exprNode in: aTMethod)
+ 					acceptsValue: exprNode
+ 					ofType: (aTMethod typeFor: argName in: self)) not]) ifTrue:
+ 				[logger
+ 					nextPutAll:
+ 						'type mismatch for formal ', argName, ' and actual ', exprNode asString,
+ 						' when inlining ', inlineSelector, ' in ', aTMethod selector, '. Use a cast.';
+ 					cr; flush]. 
+ 			exprNode]!

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 highWord sz isSmall smallVal |
- 	| 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].
  	isSmall ifTrue:
  		[smallVal := self cCoerceSimple: magnitude to: #sqInt.
  		 isNegative ifTrue: [smallVal := 0 - smallVal].
  		 ^objectMemory integerObjectOf: smallVal].
  
  	largeClass := isNegative
  					ifTrue: [objectMemory classLargeNegativeInteger]
  					ifFalse: [objectMemory classLargePositiveInteger].
  	objectMemory wordSize = 8
  		ifTrue: [sz := 8]
  		ifFalse:
  			[(highWord := magnitude >> 32) = 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.
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue:
+ 			[sz > 4 ifTrue:
+ 				[objectMemory
+ 					storeByte: 7 ofObject: newLargeInteger withValue: (magnitude >> 56 bitAnd: 16rFF);
+ 					storeByte: 6 ofObject: newLargeInteger withValue: (magnitude >> 48 bitAnd: 16rFF);
+ 					storeByte: 5 ofObject: newLargeInteger withValue: (magnitude >> 40 bitAnd: 16rFF);
+ 					storeByte: 4 ofObject: newLargeInteger withValue: (magnitude >> 32 bitAnd: 16rFF)].
+ 			objectMemory
+ 				storeByte: 3 ofObject: newLargeInteger withValue: (magnitude >> 24 bitAnd: 16rFF);
+ 				storeByte: 2 ofObject: newLargeInteger withValue: (magnitude >> 16 bitAnd: 16rFF);
+ 				storeByte: 1 ofObject: newLargeInteger withValue: (magnitude >>   8 bitAnd: 16rFF);
+ 				storeByte: 0 ofObject: newLargeInteger withValue: (magnitude ">> 0" bitAnd: 16rFF)]
+ 		ifFalse:
+ 			[sz > 4 ifTrue:
+ 				[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude >> 32].
+ 			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude].
+ 
- 	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>>primitiveConstantFill (in category 'sound primitives') -----
  primitiveConstantFill
  	"Fill the receiver, which must be an indexable bytes or words 
  	objects, with the given integer value."
  	| fillValue rcvr rcvrIsBytes end i |
  	<var: #end type: #usqInt>
  	<var: #i type: #usqInt>
  	fillValue := self positive32BitValueOf: self stackTop.
  	rcvr := self stackValue: 1.
  	self success: (objectMemory isWordsOrBytes: rcvr).
  	rcvrIsBytes := objectMemory isBytes: rcvr.
  	rcvrIsBytes ifTrue: [self success: (fillValue >= 0 and: [fillValue <= 255])].
  	self successful ifTrue:
  		[end := rcvr + (objectMemory sizeBitsOf: rcvr).
  		i := rcvr + objectMemory baseHeaderSize.
+ 		rcvrIsBytes ifTrue:
+ 			[fillValue := fillValue bitAnd: 255.
+ 			fillValue := fillValue + (fillValue << 8) + (fillValue << 16) + (fillValue << 24)].
+ 		[i < end] whileTrue:
+ 			[objectMemory long32At: i put: fillValue.
+ 			 i := i + 4].
- 		rcvrIsBytes
- 			ifTrue: [[i < end] whileTrue:
- 						[objectMemory byteAt: i put: fillValue.
- 						i := i + 1]]
- 			ifFalse: [[i < end] whileTrue:
- 						[objectMemory long32At: i put: fillValue.
- 						i := i + 4]].
  		self pop: 1]!

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
  	"N.B. will *not* cause a GC.
  	 integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
  	<notOption: #Spur64BitMemoryManager>
  	| newLargeInteger |
  	self deny: objectMemory hasSixtyFourBitImmediates.
  	(integerValue >= 0
  	 and: [objectMemory isIntegerValue: integerValue]) ifTrue:
  		[^objectMemory integerObjectOf: integerValue].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue:
+ 			[objectMemory
+ 				storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
+ 				storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
+ 				storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
+ 				storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF)]
+ 		ifFalse:
+ 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: integerValue].
- 	objectMemory
- 		storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
- 		storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
- 		storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
- 		storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF).
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>noInlineSigned32BitIntegerFor: (in category 'primitive support') -----
  noInlineSigned32BitIntegerFor: integerValue
  	"Answer a full 32 bit integer object for the given integer value."
  	<notOption: #Spur64BitMemoryManager>
  	| newLargeInteger value largeClass |
  	<inline: false>
  	(objectMemory isIntegerValue: integerValue) ifTrue:
  		[^objectMemory integerObjectOf: integerValue].
  	self deny: objectMemory hasSixtyFourBitImmediates.
  	 integerValue < 0
  		ifTrue: [largeClass := ClassLargeNegativeIntegerCompactIndex.
  				value := 0 - integerValue]
  		ifFalse: [largeClass := ClassLargePositiveIntegerCompactIndex.
  				value := integerValue].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: largeClass
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue:
+ 			[objectMemory
+ 				storeByte: 3 ofObject: newLargeInteger withValue: ((value >> 24) bitAnd: 16rFF);
+ 				storeByte: 2 ofObject: newLargeInteger withValue: ((value >> 16) bitAnd: 16rFF);
+ 				storeByte: 1 ofObject: newLargeInteger withValue: ((value >> 8) bitAnd: 16rFF);
+ 				storeByte: 0 ofObject: newLargeInteger withValue: (value bitAnd: 16rFF)]
+ 		ifFalse:
+ 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: value].
- 	objectMemory storeByte: 3 ofObject: newLargeInteger withValue: ((value >> 24) bitAnd: 16rFF).
- 	objectMemory storeByte: 2 ofObject: newLargeInteger withValue: ((value >> 16) bitAnd: 16rFF).
- 	objectMemory storeByte: 1 ofObject: newLargeInteger withValue: ((value >> 8) bitAnd: 16rFF).
- 	objectMemory storeByte: 0 ofObject: newLargeInteger withValue: (value bitAnd: 16rFF).
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>positive64BitIntegerFor: (in category 'primitive support') -----
  positive64BitIntegerFor: integerValue
  	<var: 'integerValue' type: #sqLong>
  	"Answer a Large Positive Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger highWord sz |
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
  			[(integerValue >= 0 and: [objectMemory isIntegerValue: integerValue]) ifTrue:
  				[^objectMemory integerObjectOf: integerValue].
  			 sz := 8]
  		ifFalse:
  			[(highWord := integerValue >>> 32) = 0 ifTrue:
  				[^self positive32BitIntegerFor: integerValue].
  			 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
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: 8 / objectMemory bytesPerOop.
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue:
+ 			[objectMemory
+ 				storeByte: 7 ofObject: newLargeInteger withValue: (integerValue >> 56 bitAnd: 16rFF);
+ 				storeByte: 6 ofObject: newLargeInteger withValue: (integerValue >> 48 bitAnd: 16rFF);
+ 				storeByte: 5 ofObject: newLargeInteger withValue: (integerValue >> 40 bitAnd: 16rFF);
+ 				storeByte: 4 ofObject: newLargeInteger withValue: (integerValue >> 32 bitAnd: 16rFF);
+ 				storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
+ 				storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
+ 				storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
+ 				storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF)]
+ 		ifFalse:
+ 			[objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: integerValue].
- 	objectMemory
- 		storeByte: 7 ofObject: newLargeInteger withValue: (integerValue >> 56 bitAnd: 16rFF);
- 		storeByte: 6 ofObject: newLargeInteger withValue: (integerValue >> 48 bitAnd: 16rFF);
- 		storeByte: 5 ofObject: newLargeInteger withValue: (integerValue >> 40 bitAnd: 16rFF);
- 		storeByte: 4 ofObject: newLargeInteger withValue: (integerValue >> 32 bitAnd: 16rFF);
- 		storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
- 		storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
- 		storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
- 		storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF).
  	^newLargeInteger
  !

Item was changed:
  ----- Method: StackInterpreter>>signed64BitIntegerFor: (in category 'primitive support') -----
  signed64BitIntegerFor: integerValue
  	<var: 'integerValue' type: #sqLong>
  	"Answer a Large Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger magnitude largeClass highWord sz |
  	<inline: false>
  	<var: 'magnitude' type: #sqLong>
  	<var: 'highWord' type: #usqInt>
  
  	objectMemory wordSize = 8 ifTrue:
  		[(objectMemory isIntegerValue: integerValue) ifTrue:
  			[^objectMemory integerObjectOf: integerValue].
  		 sz := 8].
  
  	integerValue < 0
  		ifTrue:[	largeClass := ClassLargeNegativeIntegerCompactIndex.
  				magnitude := 0 - integerValue]
  		ifFalse:[	largeClass := ClassLargePositiveIntegerCompactIndex.
  				magnitude := integerValue].
  
  	"Make sure to handle the most -ve value correctly. 0 - most -ve = most -ve and most -ve - 1
  	 is +ve.  Alas the simple (negative or: [integerValue - 1 < 0]) fails with contemporary gcc and icc
  	 versions with optimization and sometimes without.  The shift works on all, touch wood."
  	
  	objectMemory wordSize = 4 ifTrue:
  		[(magnitude <= 16r7FFFFFFF
  		  and: [integerValue >= 0
  			  or: [0 ~= (self cCode: [integerValue << 1]
  							inSmalltalk: [integerValue << 1 bitAnd: (1 << 64) - 1])]]) ifTrue:
  				[^self signed32BitIntegerFor: integerValue].
  
  		 (highWord := magnitude >> 32) = 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
  							eeInstantiateSmallClassIndex: largeClass
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: sz + 3 // objectMemory bytesPerOop.
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue:
+ 			[sz > 4 ifTrue:
+ 				[objectMemory
+ 					storeByte: 7 ofObject: newLargeInteger withValue: (magnitude >> 56 bitAnd: 16rFF);
+ 					storeByte: 6 ofObject: newLargeInteger withValue: (magnitude >> 48 bitAnd: 16rFF);
+ 					storeByte: 5 ofObject: newLargeInteger withValue: (magnitude >> 40 bitAnd: 16rFF);
+ 					storeByte: 4 ofObject: newLargeInteger withValue: (magnitude >> 32 bitAnd: 16rFF)].
+ 			objectMemory
+ 				storeByte: 3 ofObject: newLargeInteger withValue: (magnitude >> 24 bitAnd: 16rFF);
+ 				storeByte: 2 ofObject: newLargeInteger withValue: (magnitude >> 16 bitAnd: 16rFF);
+ 				storeByte: 1 ofObject: newLargeInteger withValue: (magnitude >>   8 bitAnd: 16rFF);
+ 				storeByte: 0 ofObject: newLargeInteger withValue: (magnitude ">> 0" bitAnd: 16rFF)]
+ 		ifFalse:
+ 			[sz > 4 ifTrue:
+ 				[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude >> 32].
+ 			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude].
- 	sz > 4 ifTrue:
- 		[objectMemory
- 			storeByte: 7 ofObject: newLargeInteger withValue: (magnitude >> 56 bitAnd: 16rFF);
- 			storeByte: 6 ofObject: newLargeInteger withValue: (magnitude >> 48 bitAnd: 16rFF);
- 			storeByte: 5 ofObject: newLargeInteger withValue: (magnitude >> 40 bitAnd: 16rFF);
- 			storeByte: 4 ofObject: newLargeInteger withValue: (magnitude >> 32 bitAnd: 16rFF)].
- 	objectMemory
- 		storeByte: 3 ofObject: newLargeInteger withValue: (magnitude >> 24 bitAnd: 16rFF);
- 		storeByte: 2 ofObject: newLargeInteger withValue: (magnitude >> 16 bitAnd: 16rFF);
- 		storeByte: 1 ofObject: newLargeInteger withValue: (magnitude >>   8 bitAnd: 16rFF);
- 		storeByte: 0 ofObject: newLargeInteger withValue: (magnitude ">> 0" bitAnd: 16rFF).
  	^newLargeInteger!

Item was changed:
  ----- Method: TMethod>>argAssignmentsFor:send:in: (in category 'inlining') -----
  argAssignmentsFor: meth send: aSendNode in: aCodeGen
  	"Return a collection of assignment nodes that assign the given argument expressions to the formal parameter variables of the given method."
  	"Optimization: If the actual parameters are either constants or local variables in the target method (the receiver), substitute them directly into the body of meth. Note that global variables cannot be subsituted because the inlined method might depend on the exact ordering of side effects to the globals."
  
  	| stmtList substitutionDict argList |
  	meth args size > (argList := aSendNode args) size ifTrue:
  		[self assert: (meth args first beginsWith: 'self_in_').
  		 argList := {aSendNode receiver}, aSendNode args].
  	
  	stmtList := OrderedCollection new: argList size.
  	substitutionDict := Dictionary new: 100.
  	meth args with: argList do:
  		[ :argName :exprNode |
  		(self isNode: exprNode substitutableFor: argName inMethod: meth in: aCodeGen)
  			ifTrue:
  				[substitutionDict
  					at: argName
+ 					put: (aCodeGen
+ 							node: exprNode
- 					put: (self node: exprNode
  							typeCompatibleWith: argName
  							inliningInto: meth selector
+ 							in: self).
- 							in: aCodeGen).
  				 locals remove: argName]
  			ifFalse:
  				[stmtList addLast:
  					(TAssignmentNode new
  						setVariable: (TVariableNode new setName: argName)
+ 						expression: (aCodeGen
+ 										node: exprNode copy
- 						expression: (self node: exprNode copy
  										typeCompatibleWith: argName
  										inliningInto: meth selector
+ 										in: self))]].
- 										in: aCodeGen))]].
  	meth parseTree: (meth parseTree bindVariablesIn: substitutionDict).
  	^stmtList!

Item was removed:
- ----- Method: TMethod>>node:typeCompatibleWith:inliningInto:in: (in category 'inlining') -----
- node: exprNode typeCompatibleWith: argName inliningInto: inlineSelector in: aCodeGen
- 	"Answer either exprNode or, iff argName is typed and exprNode is untyped, a cast of exprNode to the type of argName."
- 	| formalType actualType |
- 	^((exprNode isSend or: [exprNode isVariable])
- 	   and: [(formalType := self typeFor: argName in: aCodeGen) notNil
- 	   and: [(actualType := aCodeGen typeFor: exprNode in: self) isNil
- 			or: [(aCodeGen variableOfType: formalType acceptsValue: exprNode ofType: actualType) not]]])
- 		ifTrue: [aCodeGen nodeToCast: exprNode to: formalType]
- 		ifFalse:
- 			[((exprNode isSend or: [exprNode isVariable])
- 			  and: [(aCodeGen
- 					variableOfType: (aCodeGen typeFor: exprNode in: self)
- 					acceptsValue: exprNode
- 					ofType: (self typeFor: argName in: aCodeGen)) not]) ifTrue:
- 				[aCodeGen logger
- 					nextPutAll:
- 						'type mismatch for formal ', argName, ' and actual ', exprNode asString,
- 						' when inlining ', inlineSelector, ' in ', selector, '. Use a cast.';
- 					cr; flush]. 
- 			exprNode]!



More information about the Vm-dev mailing list