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

commits at source.squeak.org commits at source.squeak.org
Sun Feb 6 18:46:27 UTC 2022


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

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

Name: VMMaker.oscog-eem.3146
Author: eem
Time: 6 February 2022, 10:39:32.817152 am
UUID: 56a45acd-d113-4fea-9a49-4397e8bd260f
Ancestors: VMMaker.oscog-eem.3145

InterpreterPrimitives: fix the 64-bit large integer support on 32-bit platforms.

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

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 largeClassIndex 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].
  
  	largeClassIndex := isNegative
  					ifTrue: [ClassLargeNegativeIntegerCompactIndex]
  					ifFalse: [ClassLargePositiveIntegerCompactIndex].
  	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
  							eeInstantiateSmallClassIndex: largeClassIndex
  							format: (objectMemory byteFormatForNumBytes: sz)
+ 							numBytes: sz.
- 							numSlots: sz / objectMemory bytesPerOop.
  	SPURVM
  		ifTrue:
  			["Memory is eight byte aligned in SPUR, so we are sure to have room for 64bits word whatever allocated sz"
  			objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
  		ifFalse:
  			[sz > 4
  				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
  				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude)]].
  
  	^newLargeInteger!

Item was added:
+ ----- Method: NewObjectMemory>>eeInstantiateSmallClassIndex:format:numBytes: (in category 'interpreter access') -----
+ eeInstantiateSmallClassIndex: compactClassIndex format: objFormat numBytes: numBytes
+ 	"This version of instantiateClass assumes that the total object size is under
+ 	 256 bytes, the limit for objects with only one or two header words. 
+ 	 NOTE this code will only work for sizes that are an integral number of words
+ 		(hence not a 32-bit LargeInteger in a 64-bit system).
+ 	 Note that the created small object IS NOT FILLED and must be completed before returning it to Squeak.
+ 	 Since this call is used in routines that do just that we are safe. Break this rule and die in GC.
+ 	 Will *not* cause a GC. Result is guaranteed to be young."
+ 
+ 	| sizeInBytes hash header1 |
+ 	"cannot have a negative indexable field count"
+ 	self assert: (numBytes >= 0 and: [compactClassIndex ~= 0]).
+ 	self assert: (objFormat < self firstByteFormat
+ 					ifTrue: [objFormat]
+ 					ifFalse: [objFormat bitAnd: self byteFormatMask])
+ 				= (self instSpecOfClass: (self compactClassAt: compactClassIndex)).
+ 	sizeInBytes := numBytes << self shiftForWord + self baseHeaderSize.
+ 	self assert: sizeInBytes <= 252.
+ 	hash := self newObjectHash.
+ 	header1 := (objFormat << self instFormatFieldLSB
+ 					bitOr: compactClassIndex << 12)
+ 					bitOr: (hash bitAnd: HashMaskUnshifted) << HashBitsOffset.
+ 	header1 := header1 + (sizeInBytes - (header1 bitAnd: SizeMask+Size4Bit)).
+ 	^self eeAllocate: sizeInBytes headerSize: 1 h1: header1 h2: 0 h3: 0!

Item was added:
+ ----- Method: SpurMemoryManager>>eeInstantiateSmallClassIndex:format:numBytes: (in category 'instantiation') -----
+ eeInstantiateSmallClassIndex: knownClassIndex format: objFormat numBytes: numBytes
+ 	"Instantiate a small instance of a compact class.  ee stands for execution engine and
+ 	 implies that this allocation will *NOT* cause a GC.  small implies the object will have
+ 	 less than 255 slots. N.B. the instantiated object IS NOT FILLED and must be completed
+ 	 before returning it to Smalltalk. Since this call is used in routines that do just that we
+ 	 are safe.  Break this rule and die in GC.  Result is guaranteed to be young."
+ 	<inline: true>
+ 	self assert: (numBytes >= 0 and: [knownClassIndex ~= 0 and: [(self knownClassAtIndex: knownClassIndex) ~= nilObj]]).
+ 	self assert: (objFormat < self firstByteFormat
+ 					ifTrue: [objFormat]
+ 					ifFalse: [objFormat bitAnd: self byteFormatMask])
+ 				= (self instSpecOfClass: (self knownClassAtIndex: knownClassIndex)).
+ 	^self allocateSmallNewSpaceSlots: numBytes + self wordSize - 1 // self wordSize format: objFormat classIndex: knownClassIndex!



More information about the Vm-dev mailing list