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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 3 21:19:18 UTC 2015


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

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

Name: VMMaker.oscog-eem.1083
Author: eem
Time: 3 March 2015, 1:17:35.981 pm
UUID: 4d0a08c2-6218-4726-816c-1d6e3ae601d8
Ancestors: VMMaker.oscog-eem.1082

Fix disastrous typo in VMMaker.oscog-eem.1081
endianness changes.

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

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 |
  	<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: 1 ofObject: newLargeInteger withValue: magnitude >> 32].
- 				[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude >> 32].
  			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude].
  
  	^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: 1 ofObject: newLargeInteger withValue: magnitude >> 32].
- 				[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude >> 32].
  			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude].
  	^newLargeInteger!



More information about the Vm-dev mailing list