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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 16 00:08:33 UTC 2013


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

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

Name: VMMaker.oscog-eem.461
Author: eem
Time: 15 October 2013, 5:05:16.314 pm
UUID: b9156f41-92ae-4136-9d68-6ca927322513
Ancestors: VMMaker.oscog-eem.460

Update class table entries post two-way become.  class table entries
must correspond to class identityHashes, so swapping is needed if
not copyHashFlag.  Rename ...become:with:... to ...become:and:.

Simulator successfully implements e.g. Morph addInstVarName: 'foo'

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

Item was changed:
  ----- Method: SpurMemoryManager>>become:with:twoWay:copyHash: (in category 'become api') -----
  become: array1 with: array2 twoWay: twoWayFlag copyHash: copyHashFlag
  	"All references to each object in array1 are swapped with all references to the
  	 corresponding object in array2. That is, all pointers to one object are replaced
  	 with with pointers to the other. The arguments must be arrays of the same length. 
  	 Answers PrimNoErr if the primitive succeeds, otherwise a relevant error code."
  	"Implementation: Uses lazy forwarding to defer updating references until message send."
  	| ec |
  	self assert: becomeEffectsFlags = 0.
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  	(self isArray: array1) ifFalse:
  		[^PrimErrBadReceiver].
  	((self isArray: array2)
  	 and: [(self numSlotsOf: array1) = (self numSlotsOf: array2)]) ifFalse:
  		[^PrimErrBadArgument].
  	(twoWayFlag or: [copyHashFlag])
  		ifTrue:
  			[ec := self containsOnlyValidBecomeObjects: array1 and: array2]
  		ifFalse:
  			[self followForwardedObjectFields: array2 toDepth: 0.
  			ec := self containsOnlyValidBecomeObjects: array1].
  	ec ~= 0 ifTrue: [^ec].
  
  	coInterpreter preBecomeAction.
  	twoWayFlag
  		ifTrue:
+ 			[self innerBecomeObjectsIn: array1 and: array2 copyHash: copyHashFlag]
- 			[self innerBecomeObjectsIn: array1 with: array2 copyHash: copyHashFlag]
  		ifFalse:
  			[self innerBecomeObjectsIn: array1 to: array2 copyHash: copyHashFlag].
  	self postBecomeScanClassTable.
  	coInterpreter postBecomeAction: becomeEffectsFlags.
  	becomeEffectsFlags := 0.
  
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  
  	^PrimNoErr "success"!

Item was added:
+ ----- Method: SpurMemoryManager>>classAtIndex:put: (in category 'class table') -----
+ classAtIndex: classIndex put: objOop
+ 	"for become & GC of classes"
+ 	| classTablePage |
+ 	self assert: (classIndex <= self tagMask or: [classIndex >= self arrayClassIndexPun]).
+ 	self assert: (objOop = nilObj or: [(self rawHashBitsOf: objOop) = classIndex]).
+ 	classTablePage := self fetchPointer: classIndex >> self classTableMajorIndexShift
+ 							ofObject: classTableRootObj.
+ 	classTablePage = nilObj ifTrue:
+ 		[self error: 'attempt to add class to empty page'].
+ 	^self
+ 		storePointer: (classIndex bitAnd: self classTableMinorIndexMask)
+ 		ofObject: classTablePage
+ 		withValue: objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>doBecome:and:copyHash: (in category 'become implementation') -----
+ doBecome: obj1 and: obj2 copyHash: copyHashFlag
+ 	"Inner dispatch for two-way become"
+ 	<returnTypeC: #void>
+ 	| o1ClassIndex o2ClassIndex |
+ 	copyHashFlag ifFalse:
+ 		["in-lined
+ 			clasIndex := (self isInClassTable: obj) ifTrue: [self rawHashBitsOf: obj] ifFalse: [0]
+ 		 for speed."
+ 		 o1ClassIndex := self rawHashBitsOf: obj1.
+ 		 (o1ClassIndex ~= 0 and: [(self classAtIndex: o1ClassIndex) ~= obj1]) ifTrue:
+ 			[o1ClassIndex := 0].
+ 		 o2ClassIndex := self rawHashBitsOf: obj2.
+ 		 (o2ClassIndex ~= 0 and: [(self classAtIndex: o2ClassIndex) ~= obj2]) ifTrue:
+ 			[o2ClassIndex := 0]].
+ 	(self numSlotsOf: obj1) = (self numSlotsOf: obj2)
+ 		ifTrue:
+ 			[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag]
+ 		ifFalse:
+ 			[self outOfPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag].
+ 	"if copyHashFlag then nothing changes, since hashes were also swapped."
+ 	copyHashFlag ifTrue:
+ 		[^self].
+ 	"if copyHash is false then the classTable entries must be updated."
+ 	o1ClassIndex ~= 0
+ 		ifTrue:
+ 			[o2ClassIndex ~= 0
+ 				ifTrue: "both were in the table; just swap entries"
+ 					[| tmp |
+ 					 tmp := self classAtIndex: o1ClassIndex.
+ 					 self classAtIndex: o1ClassIndex put: obj2.
+ 					 self classAtIndex: o2ClassIndex put: tmp]
+ 				ifFalse: "o2 wasn't in the table; put it there"
+ 					[| newObj2 |
+ 					 newObj2 := self followForwarded: obj2.
+ 					 self assert: (self rawHashBitsOf: newObj2) = 0.
+ 					 self setHashBitsOf: newObj2 to: o1ClassIndex.
+ 					 self classAtIndex: o1ClassIndex put: newObj2]]
+ 		ifFalse:
+ 			[o2ClassIndex ~= 0 ifTrue:
+ 				[| newObj1 |
+ 				 newObj1 := self followForwarded: obj1.
+ 				 self assert: (self rawHashBitsOf: newObj1) = 0.
+ 				 self setHashBitsOf: newObj1 to: o2ClassIndex.
+ 				 self classAtIndex: o2ClassIndex put: newObj1]]!

Item was removed:
- ----- Method: SpurMemoryManager>>doBecome:with:copyHash: (in category 'become implementation') -----
- doBecome: obj1 with: obj2 copyHash: copyHashFlag
- 	((self isInClassTable: obj1)
- 	 or: [self isInClassTable: obj1]) ifTrue:
- 		[self halt].
- 	(self numSlotsOf: obj1) = (self numSlotsOf: obj2)
- 		ifTrue:
- 			[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag]
- 		ifFalse:
- 			[self outOfPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag]!

Item was changed:
  ----- Method: SpurMemoryManager>>inPlaceBecome:and:copyHashFlag: (in category 'become implementation') -----
  inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag
  	"Do become in place by swapping object contents."
  	| headerTemp temp1 temp2 o1HasYoung o2HasYoung |
  	<var: 'headerTemp' type: #usqLong>
  	self assert: (self numSlotsOf: obj1) = (self numSlotsOf: obj2).
  	"swap headers, but swapping headers swaps remembered bits;
  	 these need to be unswapped."
  	temp1 := self isRemembered: obj1.
  	temp2 := self isRemembered: obj2.
  	headerTemp := self longLongAt: obj1.
  	self longLongAt: obj1 put: (self longLongAt: obj2).
  	self longLongAt: obj2 put: headerTemp.
  	self setIsRememberedOf: obj1 to: temp1.
  	self setIsRememberedOf: obj2 to: temp2.
+ 	"swapping headers swaps hash; if !!copyHashFlag undo hash copy"
- 	"swapping headers swaps hash; if !!copyHashFlagundo hash copy"
  	copyHashFlag ifFalse:
  		[temp1 := self rawHashBitsOf: obj1.
  		 self setHashBitsOf: obj1 to: (self rawHashBitsOf: obj2).
  		 self setHashBitsOf: obj2 to: temp1].
  	o1HasYoung := o2HasYoung := false.
  	0 to: (self numSlotsOf: obj1) - 1 do:
  		[:i|
  		temp1 := self fetchPointer: i ofObject: obj1.
  		temp2 := self fetchPointer: i ofObject: obj2.
  		self storePointerUnchecked: i
  			ofObject: obj1
  			withValue: temp2.
  		self storePointerUnchecked: i
  			ofObject: obj2
  			withValue: temp1.
  		((self isNonImmediate: temp2) and: [self isYoung: temp2]) ifTrue:
  			[o1HasYoung := true].
  		((self isNonImmediate: temp1) and: [self isYoung: temp1]) ifTrue:
  			[o2HasYoung := true]].
  	(self isYoung: obj1) ifFalse:
  		[o1HasYoung ifTrue:
  			[self possibleRootStoreInto: obj1]].
  	(self isYoung: obj2) ifFalse:
  		[o2HasYoung ifTrue:
  			[self possibleRootStoreInto: obj2]]!

Item was added:
+ ----- Method: SpurMemoryManager>>innerBecomeObjectsIn:and:copyHash: (in category 'become implementation') -----
+ innerBecomeObjectsIn: array1 and: array2 copyHash: copyHashFlag
+ 	"Inner loop of two-way become."
+ 	0 to: (self numSlotsOf: array1) - 1 do:
+ 		[:i| | obj1 obj2 |
+ 		obj1 := self fetchPointer: i ofObject: array1.
+ 		obj2 := self fetchPointer: i ofObject: array2.
+ 		self doBecome: obj1 and: obj2 copyHash: copyHashFlag.
+ 		(self isForwarded: obj1) ifTrue:
+ 			[obj1 := self followForwarded: obj1.
+ 			 self storePointer: i ofObject: array1 withValue: obj1].
+ 		(self isForwarded: obj2) ifTrue:
+ 			[obj2 := self followForwarded: obj2.
+ 			 self storePointer: i ofObject: array2 withValue: obj2]]!

Item was removed:
- ----- Method: SpurMemoryManager>>innerBecomeObjectsIn:with:copyHash: (in category 'become implementation') -----
- innerBecomeObjectsIn: array1 with: array2 copyHash: copyHashFlag
- 	"Inner loop of two-way become."
- 	0 to: (self numSlotsOf: array1) - 1 do:
- 		[:i| | obj1 obj2 |
- 		obj1 := self fetchPointer: i ofObject: array1.
- 		obj2 := self fetchPointer: i ofObject: array2.
- 		self doBecome: obj1 with: obj2 copyHash: copyHashFlag.
- 		(self isForwarded: obj1) ifTrue:
- 			[obj1 := self followForwarded: obj1.
- 			 self storePointer: i ofObject: array1 withValue: obj1].
- 		(self isForwarded: obj2) ifTrue:
- 			[obj2 := self followForwarded: obj2.
- 			 self storePointer: i ofObject: array2 withValue: obj2]]!

Item was changed:
+ ----- Method: SpurMemoryManager>>isInClassTable: (in category 'class table') -----
- ----- Method: SpurMemoryManager>>isInClassTable: (in category 'become implementation') -----
  isInClassTable: objOop
  	| hash |
  	hash := self rawHashBitsOf: objOop.
  	hash = 0 ifTrue:
  		[false].
  	^(self classAtIndex: hash) = objOop!



More information about the Vm-dev mailing list