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

commits at source.squeak.org commits at source.squeak.org
Fri Mar 21 11:47:49 UTC 2014


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

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

Name: VMMaker.oscog-eem.654
Author: eem
Time: 21 March 2014, 4:43:36.879 am
UUID: 0b86152b-2ab0-40e7-a54b-b2abc4e53e64
Ancestors: VMMaker.oscog-eem.653

Streamline copyAndForward: and forward[Survivor]:to: and clients
of setFormatOf:to: & setClassIndexOf:to:.

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

Item was changed:
  ----- Method: Spur32BitMemoryManager>>changeClassOf:to: (in category 'interpreter access') -----
  changeClassOf: rcvr to: argClass
  	"Attempt to change the class of the receiver to the argument given that the
  	 format of the receiver matches the format of the argument.  If successful,
  	 answer 0, otherwise answer an error code indicating the reason for failure. 
  	 Fail if the format of the receiver is incompatible with the format of the argument,
  	 or if the argument is a fixed class and the receiver's size differs from the size
  	 that an instance of the argument should have."
  	<inline: false>
  	| classFormat fixedFields instFormat normalizedInstFormat newFormat classIndex |
  	classFormat := self formatOfClass: argClass.
  	fixedFields := self fixedFieldsOfClassFormat: classFormat.
  	classFormat := self instSpecOfClassFormat: classFormat.
  	instFormat := self formatOf: rcvr.
  	normalizedInstFormat := self classFormatForInstanceFormat: instFormat.
  
  	(normalizedInstFormat > self lastPointerFormat
  	 and: [normalizedInstFormat = classFormat])
  		ifTrue: [newFormat := instFormat]
  		ifFalse:
  			[normalizedInstFormat <= self lastPointerFormat
  				ifTrue:
  					[classFormat > self lastPointerFormat ifTrue:
  						[^PrimErrInappropriate].
  					 (self numSlotsOf: rcvr) < fixedFields ifTrue:
  						[^PrimErrBadReceiver].
  					 newFormat := classFormat]
  				ifFalse:
  					[| instBytes |
  					instBytes := self byteLengthOf: rcvr.
  					normalizedInstFormat caseOf: {
  						[self sixtyFourBitIndexableFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := classFormat].
  						[self firstLongFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 (classFormat = self sixtyFourBitIndexableFormat and: [instBytes anyMask: 1]) ifTrue:
  								[^PrimErrBadReceiver].
  							 newFormat := classFormat].
  						[self firstShortFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstByteFormat] 		
  									-> [newFormat := classFormat + (4 - instBytes bitAnd: 3)] }].
  						[self firstByteFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver]].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver]].
  								[self firstShortFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver]] }.
  							 newFormat := classFormat].
  						[self firstCompiledMethodFormat] ->
  							[classFormat ~= self firstCompiledMethodFormat ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := instFormat] }]].
  
  	(classIndex := self ensureBehaviorHash: argClass) < 0 ifTrue:
  		[^classIndex negated].
+ 	self set: rcvr classIndexTo: classIndex formatTo: newFormat.
- 
- 	self setFormatOf: rcvr to: newFormat;
- 		setClassIndexOf: rcvr to: classIndex.
  	"ok"
  	^0!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>set:classIndexTo:formatTo: (in category 'header access') -----
+ set: objOop classIndexTo: classIndex formatTo: format
+ 	"0 = 0 sized objects (UndefinedObject True False et al)
+ 	 1 = non-indexable objects with inst vars (Point et al)
+ 	 2 = indexable objects with no inst vars (Array et al)
+ 	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 	 4 = weak indexable objects with inst vars (WeakArray et al)
+ 	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 	 6 unused, reserved for exotic pointer objects?
+ 	 7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 	 8 unused, reserved for exotic non-pointer objects?
+ 	 9 (?) 64-bit indexable
+ 	 10 - 11 32-bit indexable
+ 	 12 - 15 16-bit indexable
+ 	 16 - 23 byte indexable
+ 	 24 - 31 compiled method"
+ 	<inline: true>
+ 	self assert: (classIndex between: 0 and: self classIndexMask).
+ 	self assert: (format between: 0 and: self formatMask).
+ 	self flag: #endianness.
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift + self classIndexMask) bitInvert32)
+ 			+ (classIndex
+ 			+  (format << self formatShift))!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>changeClassOf:to: (in category 'interpreter access') -----
  changeClassOf: rcvr to: argClass
  	"Attempt to change the class of the receiver to the argument given that the
  	 format of the receiver matches the format of the argument.  If successful,
  	 answer 0, otherwise answer an error code indicating the reason for failure. 
  	 Fail if the format of the receiver is incompatible with the format of the argument,
  	 or if the argument is a fixed class and the receiver's size differs from the size
  	 that an instance of the argument should have."
  	<inline: false>
  	| classFormat fixedFields instFormat normalizedInstFormat newFormat classIndex |
  	classFormat := self formatOfClass: argClass.
  	fixedFields := self fixedFieldsOfClassFormat: classFormat.
  	classFormat := self instSpecOfClassFormat: classFormat.
  	instFormat := self formatOf: rcvr.
  	normalizedInstFormat := self classFormatForInstanceFormat: instFormat.
  
  	(normalizedInstFormat > self lastPointerFormat
  	 and: [normalizedInstFormat = classFormat])
  		ifTrue: [newFormat := instFormat]
  		ifFalse:
  			[normalizedInstFormat <= self lastPointerFormat
  				ifTrue:
  					[classFormat > self lastPointerFormat ifTrue:
  						[^PrimErrInappropriate].
  					 (self numSlotsOf: rcvr) < fixedFields ifTrue:
  						[^PrimErrBadReceiver].
  					 newFormat := classFormat]
  				ifFalse:
  					[| instBytes |
  					instBytes := self byteLengthOf: rcvr.
  					normalizedInstFormat caseOf: {
  						[self sixtyFourBitIndexableFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := classFormat].
  						[self firstLongFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 (classFormat = self sixtyFourBitIndexableFormat and: [instBytes anyMask: 1]) ifTrue:
  								[^PrimErrBadReceiver].
  							 newFormat := classFormat].
  						[self firstShortFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (2 - instBytes bitAnd: 1)].
  								[self firstByteFormat] 		
  									-> [newFormat := classFormat + (8 - instBytes bitAnd: 7)] }].
  						[self firstByteFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (2 - instBytes bitAnd: 1)].
  								[self firstShortFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (4 - instBytes bitAnd: 3)] }.
  							 newFormat := classFormat].
  						[self firstCompiledMethodFormat] ->
  							[classFormat ~= self firstCompiledMethodFormat ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := instFormat] }]].
  
  	(classIndex := self ensureBehaviorHash: argClass) < 0 ifTrue:
  		[^classIndex negated].
+ 	self set: rcvr classIndexTo: classIndex formatTo: newFormat.
- 
- 	self setFormatOf: rcvr to: newFormat;
- 		setClassIndexOf: rcvr to: classIndex.
  	"ok"
  	^0!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>set:classIndexTo:formatTo: (in category 'header access') -----
+ set: objOop classIndexTo: classIndex formatTo: format
+ 	"0 = 0 sized objects (UndefinedObject True False et al)
+ 	 1 = non-indexable objects with inst vars (Point et al)
+ 	 2 = indexable objects with no inst vars (Array et al)
+ 	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 	 4 = weak indexable objects with inst vars (WeakArray et al)
+ 	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 	 6 unused, reserved for exotic pointer objects?
+ 	 7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 	 8 unused, reserved for exotic non-pointer objects?
+ 	 9 (?) 64-bit indexable
+ 	 10 - 11 32-bit indexable
+ 	 12 - 15 16-bit indexable
+ 	 16 - 23 byte indexable
+ 	 24 - 31 compiled method"
+ 	<inline: true>
+ 	self assert: (classIndex between: 0 and: self classIndexMask).
+ 	self assert: (format between: 0 and: self formatMask).
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift + self classIndexMask) bitInvert64)
+ 			+ (classIndex
+ 			+  (format << self formatShift))!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	"copyAndForward: survivor copies a survivor object either to
  	 futureSurvivorSpace or, if it is to be promoted, to oldSpace.
  	 It leaves a forwarding pointer behind.  If the object is weak
  	 then corpse is threaded onto the weakList for later treatment."
  	<inline: false>
+ 	| bytesInObj format newLocation |
- 	| bytesInObj newLocation hash |
  	self assert: ((manager isInEden: survivor) "cog methods should be excluded."
  				or: [manager isInPastSpace: survivor]).
  	bytesInObj := manager bytesInObject: survivor.
+ 	format := manager formatOf: survivor.
- 	"Must remember hash before copying because threading
- 	 on to the weak & ephemeron lists smashes the hash field."
- 	hash := manager rawHashBitsOf: survivor.
  	((self shouldBeTenured: survivor)
  	 or: [futureSurvivorStart + bytesInObj > futureSpace limit])
+ 		ifTrue: [newLocation := self copyToOldSpace: survivor bytes: bytesInObj format: format]
- 		ifTrue: [newLocation := self copyToOldSpace: survivor]
  		ifFalse: [newLocation := self copyToFutureSpace: survivor bytes: bytesInObj].
- 	hash ~= 0 ifTrue:
- 		[manager setHashBitsOf: newLocation to: hash].
  	manager forwardSurvivor: survivor to: newLocation.
  	"if weak or ephemeron add to the relevant list for subsequent scanning."
+ 	(manager isWeakFormat: format) ifTrue:
- 	(manager isWeakNonImm: newLocation) ifTrue:
  		[self addToWeakList: survivor].
+ 	((manager isEphemeronFormat: format)
- 	((manager isEphemeron: newLocation)
  	 and: [(self isScavengeSurvivor: (manager keyOfEphemeron: newLocation)) not]) ifTrue:
  		[self addToEphemeronList: survivor].
  	^newLocation!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyToOldSpace: (in category 'scavenger') -----
  copyToOldSpace: survivor
  	"Copy survivor to oldSpace.  Answer the new oop of the object."
  	<inline: true>
+ 	| nTenures numSlots hash newOop |
- 	| nTenures numSlots newOop |
  	nTenures := statTenures.
  	self flag: 'why not just pass header??'.
  	numSlots := manager numSlotsOf: survivor.
+ 	hash := manager rawHashBitsOf: survivor.
  	newOop := manager
  					allocateSlotsInOldSpace: numSlots
  					format: (manager formatOf: survivor)
  					classIndex: (manager classIndexOf: survivor).
  	newOop ifNil:
  		[manager growOldSpaceByAtLeast: 0. "grow by growHeadroom"
  		 newOop := manager
  					allocateSlotsInOldSpace: numSlots
  					format: (manager formatOf: survivor)
  					classIndex: (manager classIndexOf: survivor).
  		 newOop ifNil:
  			[self error: 'out of memory']].
  	manager
  		mem: (newOop + manager baseHeaderSize) asVoidPointer
  		cp: (survivor + manager baseHeaderSize) asVoidPointer
  		y: numSlots * manager wordSize.
+ 	(manager hasPointerFields: survivor) ifTrue:
+ 		[self remember: newOop.
+ 		 manager setIsRememberedOf: newOop to: true].
+ 	hash ~= 0 ifTrue:
+ 		[manager setHashBitsOf: newOop to: hash].
- 	self remember: newOop.
- 	manager setIsRememberedOf: newOop to: true.
  	statTenures := nTenures + 1.
  	^newOop!

Item was added:
+ ----- Method: SpurGenerationScavenger>>copyToOldSpace:bytes: (in category 'scavenger') -----
+ copyToOldSpace: survivor bytes: bytesInObject
+ 	"Copy survivor to oldSpace.  Answer the new oop of the object."
+ 	<inline: true>
+ 	| nTenures startOfSurvivor newStart newOop |
+ 	nTenures := statTenures.
+ 	startOfSurvivor := manager startOfObject: survivor.
+ 	newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
+ 	newStart ifNil:
+ 		[manager growOldSpaceByAtLeast: 0. "grow by growHeadroom"
+ 		 newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
+ 		 newStart ifNil:
+ 			[self error: 'out of memory']].
+ 	manager checkFreeSpace.
+ 	manager mem: newStart asVoidPointer cp: startOfSurvivor asVoidPointer y: bytesInObject.
+ 	newOop := newStart + (survivor - startOfSurvivor).
+ 	(manager hasPointerFields: survivor) ifTrue:
+ 		[self remember: newOop.
+ 		 manager setIsRememberedOf: newOop to: true].
+ 	statTenures := nTenures + 1.
+ 	^newOop!

Item was added:
+ ----- Method: SpurGenerationScavenger>>copyToOldSpace:bytes:format: (in category 'scavenger') -----
+ copyToOldSpace: survivor bytes: bytesInObject format: formatOfSurvivor
+ 	"Copy survivor to oldSpace.  Answer the new oop of the object."
+ 	<inline: true>
+ 	| nTenures startOfSurvivor newStart newOop |
+ 	self assert: (formatOfSurvivor = (manager formatOf: survivor)
+ 				and: [(manager isMarked: survivor) not
+ 				and: [(manager isPinned: survivor) not
+ 				and: [(manager isRemembered: survivor) not]]]).
+ 	nTenures := statTenures.
+ 	startOfSurvivor := manager startOfObject: survivor.
+ 	newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
+ 	newStart ifNil:
+ 		[manager growOldSpaceByAtLeast: 0. "grow by growHeadroom"
+ 		 newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
+ 		 newStart ifNil:
+ 			[self error: 'out of memory']].
+ 	manager checkFreeSpace.
+ 	manager mem: newStart asVoidPointer cp: startOfSurvivor asVoidPointer y: bytesInObject.
+ 	newOop := newStart + (survivor - startOfSurvivor).
+ 	(manager isAnyPointerFormat: formatOfSurvivor) ifTrue:
+ 		[self remember: newOop.
+ 		 manager setIsRememberedOf: newOop to: true].
+ 	statTenures := nTenures + 1.
+ 	^newOop!

Item was changed:
  ----- Method: SpurMemoryManager>>allInstancesOf: (in category 'primitive support') -----
  allInstancesOf: aClass
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of instances as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| classIndex freeChunk ptr start limit count bytes |
  	classIndex := self rawHashBitsOf: aClass.
  	(classIndex = 0
  	 or: [aClass ~~ (self classOrNilAtIndex: classIndex)]) ifTrue:
  		[freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 ^freeChunk].
  	self markObjects. "don't want to revive objects unnecessarily."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (self isMarked: obj) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[self setIsMarkedOf: obj to: false.
  					 (self classIndexOf: obj) = classIndex ifTrue:
  					 	[count := count + 1.
  						 ptr < limit ifTrue:
  							[self longAt: ptr put: obj.
  							 ptr := ptr + self bytesPerSlot]]]
  				ifFalse:
  					[(self isSegmentBridge: obj) ifFalse:
  						[self setIsMarkedOf: obj to: false]]]].
  	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
  	self emptyObjStack: weaklingStack.
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeObject: freeChunk.
  		 ^self integerObjectOf: count].
  	count < self numSlotsMask ifTrue:
  		[| smallObj |
  		 smallObj := self allocateSlots: count format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 0 to: count - 1 do:
  			[:i|
  			self storePointerUnchecked: i ofObject: smallObj withValue: (self fetchPointer: i ofObject: freeChunk)].
  		 self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self beRootIfOld: smallObj.
  		 self checkFreeSpace.
  		 ^smallObj].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
+ 	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
- 	self setClassIndexOf: freeChunk to: ClassArrayCompactIndex.
- 	self setFormatOf: freeChunk to: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	^freeChunk
  	
  	!

Item was changed:
  ----- Method: SpurMemoryManager>>allObjects (in category 'primitive support') -----
  allObjects
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of objects as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| freeChunk ptr start limit count bytes |
  	self markObjects. "don't want to revive objects unnecessarily."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (self isMarked: obj) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[self setIsMarkedOf: obj to: false.
  					 count := count + 1.
  					 ptr < limit ifTrue:
  						[self longAt: ptr put: obj.
  						 ptr := ptr + self bytesPerSlot]]
  				ifFalse:
  					[(self isSegmentBridge: obj) ifFalse:
  						[self setIsMarkedOf: obj to: false]]]].
  	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
  	self emptyObjStack: weaklingStack.
  	self assert: count >= self numSlotsMask.
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self checkFreeSpace.
  		 ^self integerObjectOf: count].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
+ 	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
- 	self setClassIndexOf: freeChunk to: ClassArrayCompactIndex.
- 	self setFormatOf: freeChunk to: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	^freeChunk
  	
  	!

Item was changed:
  ----- Method: SpurMemoryManager>>forward:to: (in category 'become implementation') -----
  forward: obj1 to: obj2
+ 	self set: obj1 classIndexTo: self isForwardedObjectClassIndexPun formatTo: self forwardedFormat.
- 	self setFormatOf: obj1 to: self forwardedFormat.
- 	self setClassIndexOf: obj1 to: self isForwardedObjectClassIndexPun.
  	self storePointer: 0 ofForwarder: obj1 withValue: obj2!

Item was changed:
  ----- Method: SpurMemoryManager>>forwardSurvivor:to: (in category 'become implementation') -----
  forwardSurvivor: obj1 to: obj2
+ 	"This version of forward:to: can use an uncecked store because it is known that obj1 is young."
  	self assert: (self isInNewSpace: obj1).
  	self assert: ((self isInFutureSpace: obj2) or: [self isInOldSpace: obj2]).
  	self storePointerUnchecked: 0 ofObject: obj1 withValue: obj2.
+ 	self set: obj1 classIndexTo: self isForwardedObjectClassIndexPun formatTo: self forwardedFormat!
- 	self setFormatOf: obj1 to: self forwardedFormat.
- 	self setClassIndexOf: obj1 to: self isForwardedObjectClassIndexPun!

Item was changed:
  ----- Method: SpurMemoryManager>>hasPointerFields: (in category 'object testing') -----
  hasPointerFields: oop
  	<inline: true>
- 	| format |
  	^(self isNonImmediate: oop)
+ 	  and: [self hasPointerFieldsNonImm: oop]!
- 	  and: [(format := self formatOf: oop) <= self lastPointerFormat
- 		   or: [format >= self firstCompiledMethodFormat]]!

Item was added:
+ ----- Method: SpurMemoryManager>>hasPointerFieldsNonImm: (in category 'object testing') -----
+ hasPointerFieldsNonImm: oop
+ 	<inline: true>
+ 	^self isAnyPointerFormat: (self formatOf: oop)!

Item was added:
+ ----- Method: SpurMemoryManager>>isAnyPointerFormat: (in category 'header formats') -----
+ isAnyPointerFormat: format
+ 	"the inverse of isPureBitsFormat:"
+ 	<inline: true>
+ 	^format <= self lastPointerFormat or: [format >= self firstCompiledMethodFormat]!

Item was changed:
  ----- Method: SpurMemoryManager>>isEphemeron: (in category 'object testing') -----
  isEphemeron: objOop
  	self assert: (self isNonImmediate: objOop).
+ 	^self isEphemeronFormat: (self formatOf: objOop)!
- 	^(self formatOf: objOop) = self ephemeronFormat!

Item was added:
+ ----- Method: SpurMemoryManager>>isEphemeronFormat: (in category 'header formats') -----
+ isEphemeronFormat: format
+ 	<inline: true>
+ 	^format = self ephemeronFormat!

Item was changed:
+ ----- Method: SpurMemoryManager>>isIndexableFormat: (in category 'header formats') -----
- ----- Method: SpurMemoryManager>>isIndexableFormat: (in category 'object testing') -----
  isIndexableFormat: format
  	^format >= self arrayFormat
  	  and: [format <= self weakArrayFormat
  			or: [format >= self sixtyFourBitIndexableFormat]]!

Item was changed:
+ ----- Method: SpurMemoryManager>>isPointersFormat: (in category 'header formats') -----
- ----- Method: SpurMemoryManager>>isPointersFormat: (in category 'object testing') -----
  isPointersFormat: format
  	^format <= self lastPointerFormat!

Item was changed:
  ----- Method: SpurMemoryManager>>isPureBitsFormat: (in category 'header formats') -----
  isPureBitsFormat: format
+ 	"the inverse of isAnyPointerFormat:"
  	^format >= self sixtyFourBitIndexableFormat
  	  and: [format < self firstCompiledMethodFormat]!

Item was added:
+ ----- Method: SpurMemoryManager>>isWeakFormat: (in category 'header formats') -----
+ isWeakFormat: format
+ 	<inline: true>
+ 	^format = self weakArrayFormat!

Item was changed:
  ----- Method: SpurMemoryManager>>isWeakNonImm: (in category 'object testing') -----
  isWeakNonImm: objOop
+ 	<inline: true>
+ 	^self isWeakFormat: (self formatOf: objOop)!
- 	^(self formatOf: objOop) = self weakArrayFormat!

Item was added:
+ ----- Method: SpurMemoryManager>>set:classIndexTo:formatTo: (in category 'header access') -----
+ set: objOop classIndexTo: classIndex formatTo: format
+ 	"0 = 0 sized objects (UndefinedObject True False et al)
+ 	 1 = non-indexable objects with inst vars (Point et al)
+ 	 2 = indexable objects with no inst vars (Array et al)
+ 	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 	 4 = weak indexable objects with inst vars (WeakArray et al)
+ 	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 	 6 unused, reserved for exotic pointer objects?
+ 	 7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 	 8 unused, reserved for exotic non-pointer objects?
+ 	 9 (?) 64-bit indexable
+ 	 10 - 11 32-bit indexable
+ 	 12 - 15 16-bit indexable
+ 	 16 - 23 byte indexable
+ 	 24 - 31 compiled method"
+ 	self subclassResponsibility!



More information about the Vm-dev mailing list