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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 6 00:02:49 UTC 2013


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

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

Name: VMMaker.oscog-eem.500
Author: eem
Time: 5 November 2013, 4:00:30.969 pm
UUID: 72bc8825-af12-430c-96ad-be11ea0330a2
Ancestors: VMMaker.oscog-eem.499

Fix fetchPointer:ofObject: assert for forwarders and free objs,
followForwardedObjectFields:toDepth: for CompiledMethods, and
forwardSurvivor:to: for tenured objs.

Remember to invoke the method that scans the class table post
compact.

Fix bug in markAndTrace: with objs indexed from mark stack
(could get caught in an infinite loop).

Fix several bugs in SpurCircularBuffer.

Fix bug in exactFitCompact.

Fix BalloonEngineSImulation by ensuring that workBuffer is initialized
with 0s not nils.

Global GC appears functional.

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

Item was changed:
  ----- Method: BalloonEngineSimulation>>workBufferPut: (in category 'simulation') -----
  workBufferPut: wbOop
  	interpreterProxy isInterpreterProxy 
  		ifTrue:[^super workBufferPut: wbOop].
  	workBuffer := ((interpreterProxy firstIndexableField: wbOop) as: BalloonArray) asCArrayAccessor.
  	workBufferArray ifNil:
+ 		[workBufferArray := Array new: (interpreterProxy slotSizeOf: wbOop) withAll: 0].
- 		[workBufferArray := Array new: (interpreterProxy slotSizeOf: wbOop)].
  	workBuffer getObject setSimArray: workBufferArray!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>fetchPointer:ofObject: (in category 'object access') -----
  fetchPointer: fieldIndex ofObject: objOop
  	self assert: (self isForwarded: objOop) not.
+ 	self assert: (fieldIndex >= 0 and: [fieldIndex < (self numSlotsOfAny: objOop)
+ 				or: [fieldIndex = 0 "forwarders and free objs"]]).
- 	self assert: (fieldIndex >= 0 and: [fieldIndex < (self numSlotsOfAny: objOop)]).
  	^super fetchPointer: fieldIndex ofObject: objOop!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>setIsMarkedOf:to: (in category 'header access') -----
  setIsMarkedOf: objOop to: aBoolean
  	super setIsMarkedOf: objOop to: aBoolean.
+ 	"(aBoolean
- 	(aBoolean
  	 and: [(self isContextNonImm: objOop)
  	 and: [(coInterpreter
  			checkIsStillMarriedContext: objOop
  			currentFP: coInterpreter framePointer)
  	 and: [(coInterpreter stackPages stackPageFor: (coInterpreter frameOfMarriedContext: objOop)) trace = 0]]]) ifTrue:
+ 		[self halt]"!
- 		[self halt]!

Item was changed:
  ----- Method: SpurCircularBuffer>>addLast: (in category 'accessing') -----
  addLast: element
  	| newLast |
  	newLast := last + manager wordSize.
+ 	newLast >= limit ifTrue:
- 	newLast > limit ifTrue:
  		[newLast := start].
  	(newLast = first and: [last >= start]) ifTrue: "wrapped; bump first"
  		[(first := newLast + manager wordSize) >= limit ifTrue:
  			[first := start]].
  	last := newLast.
+ 	self assert: (first >= start and: [first < limit]).
+ 	self assert: (last >= start and: [last < limit]).
  	manager longAt: newLast put: element!

Item was changed:
  ----- Method: SpurCircularBuffer>>from:reverseDo: (in category 'enumerating') -----
  from: initialPtr reverseDo: aBlock
  	<inline: true>
  	| ptr |
  	last >= start ifTrue:
  		[ptr := initialPtr.
+ 		 first <= last
+ 			ifTrue: "enum in first to last range, last to first"
+ 				[ptr >= first ifTrue:
+ 					[[aBlock value: (manager longAt: ptr).
+ 					  (ptr := ptr - manager wordSize) < first ifTrue:
+ 						[^nil]] repeat]]
+ 			ifFalse: "enum in start to last range, last to start"
+ 				[ptr <= last ifTrue:
+ 					[[ptr >= start] whileTrue:
+ 						[aBlock value: (manager longAt: ptr).
+ 						 ptr := ptr - manager wordSize].
+ 					 ptr := limit].
+ 				 "now enum in first to limit range, limit to first"
+ 				 [ptr >= first] whileTrue:
+ 					[aBlock value: (manager longAt: ptr).
+ 					 ptr := ptr - manager wordSize]]].
- 		 [aBlock value: (manager longAt: ptr).
- 		  ptr = first ifTrue: [^nil].
- 		  (ptr := ptr - manager wordSize) < start ifTrue:
- 			[ptr := limit]] repeat].
  	^nil!

Item was added:
+ ----- Method: SpurCircularBuffer>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	<doNotGenerate>
+ 	super printOn: aStream.
+ 	first ifNotNil:
+ 		[aStream nextPutAll: ' first: '; nextPutAll: first hex].
+ 	last ifNotNil:
+ 		[aStream nextPutAll: ' last: '; nextPutAll: last hex]!

Item was changed:
  ----- Method: SpurCircularBuffer>>reverseDo: (in category 'enumerating') -----
  reverseDo: aBlock
  	| ptr |
  	last >= start ifTrue:
  		[ptr := last.
+ 		 [self assert: (first <= last
+ 						ifTrue: [first <= ptr and: [ptr <= last]]
+ 						ifFalse: [(start <= ptr and: [ptr <= last]) or: [first <= ptr and: [ptr < limit]]]).
+ 		  aBlock value: (manager longAt: ptr).
- 		 [aBlock value: (manager longAt: ptr).
  		  ptr = first ifTrue: [^nil].
  		  (ptr := ptr - manager wordSize) < start ifTrue:
  			[ptr := limit]] repeat].
  	^nil!

Item was changed:
  ----- Method: SpurMemoryManager>>exactFitCompact (in category 'compaction') -----
  exactFitCompact
  	"Compact all of memory above firstFreeChunk using exact-fit, assuming free
  	 space is sorted and that the highest objects are recorded in highestObjects.
  	 Note that we don't actually move; we merely copy and forward.  Eliminating
+ 	 forwarders will be done in a final pass.  Leave the objects that don't fit
+ 	 exactly (the misfits), and hence aren't moved, in highestObjects."
- 	 forwarders will be done in a final pass.
- 	 Leave the objects that don't fit exactly, and hence aren't moved, in highestObjects."
  
  	<inline: false>
  	| misfits first |
  	<var: #misfits type: #usqInt>
  	totalFreeOldSpace = 0 ifTrue: [^self].
  	misfits := highestObjects last + self wordSize.
  	[statCompactPassCount := statCompactPassCount + 1.
  	 highestObjects from: misfits - self wordSize reverseDo:
  		[:o| | b |
  		o < firstFreeChunk ifTrue:
  			[misfits = (highestObjects last + self wordSize)
  				ifTrue: [highestObjects resetAsEmpty]
  				ifFalse: [highestObjects first: misfits].
  			 ^self].
  		 ((self isForwarded: o) or: [self isPinned: o]) ifFalse:
  			[b := self bytesInObject: o.
  			 (self allocateOldSpaceChunkOfExactlyBytes: b suchThat: [:f| f < o])
  				ifNil:
  					[misfits := misfits - self wordSize.
  					 misfits < highestObjects start ifTrue:
+ 						[misfits := highestObjects limit - self wordSize].
- 						[misfits := highestObjects limit].
  					 self longAt: misfits put: o]
  				ifNotNil:
  					[:f| self copyAndForward: o withBytes: b toFreeChunk: f]]].
  	 "now highestObjects contains only misfits, if any, from misfits to last.
  	  set first to first failure and refill buffer. next cycle will add more misfits.
  	  give up on exact-fit when half of the highest objects fail to fit."
  	 first := self longAt: highestObjects first.
  	 first > firstFreeChunk ifTrue:
  		[| highestObjBytes failureBytes savedLimit |
  		 highestObjBytes := highestObjects limit - highestObjects start.
  		 failureBytes := highestObjects last >= misfits
  							ifTrue: [highestObjects last - misfits]
  							ifFalse: [highestObjBytes - (misfits - highestObjects last)].
  		 failureBytes >= (highestObjBytes // 2) ifTrue:
  			[highestObjects first: misfits.
  			 ^self].
  		 savedLimit := self moveMisfitsToTopOfHighestObjects: misfits.
  		 self fillHighestObjectsWithMovableObjectsFrom: firstFreeChunk upTo: first.
  		 misfits := self moveMisfitsInHighestObjectsBack: savedLimit]] repeat!

Item was changed:
  ----- Method: SpurMemoryManager>>followForwardedObjectFields:toDepth: (in category 'become api') -----
  followForwardedObjectFields: objOop toDepth: depth
  	"follow pointers in the object to depth.
  	 How to avoid cyclic structures?? A temproary mark bit?"
  	| oop |
+ 	self assert: ((self isPointers: objOop) or: [self isOopCompiledMethod: objOop]).
- 	self assert: (self isPointers: objOop).
  	0 to: (self numSlotsOf: objOop) - 1 do:
  		[:i|
  		oop := self fetchPointer: i ofObject: objOop.
  		((self isNonImmediate: oop)
  		 and: [self isForwarded: oop]) ifTrue:
  			[oop := self followForwarded: oop.
  			self storePointer: i ofObject: objOop withValue: oop].
  		depth > 0 ifTrue:
  			[self followForwardedObjectFields: objOop toDepth: depth - 1]]!

Item was changed:
  ----- Method: SpurMemoryManager>>forwardSurvivor:to: (in category 'become implementation') -----
  forwardSurvivor: obj1 to: obj2
  	self assert: (self isInNewSpace: obj1).
+ 	self assert: ((self isInFutureSpace: obj2) or: (self isInOldSpace: obj2)).
- 	self assert: (self isInFutureSpace: obj2).
  	self storePointerUnchecked: 0 ofObject: obj1 withValue: obj2.
  	self setFormatOf: obj1 to: self forwardedFormat.
  	self setClassIndexOf: obj1 to: self isForwardedObjectClassIndexPun!

Item was changed:
  ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
  globalGarbageCollect
  	self runLeakCheckerForFullGC: true.
  	self assert: self validObjStacks.
  	self markObjects.
  	self nilUnmarkedWeaklingSlots.
  	self freeUnmarkedObjectsAndSortAndCoalesceFreeSpace.
  	self bestFitCompact.
+ 	self postCompactScanClassTable.
  	self eliminateAndFreeForwarders.
  	self assert: self validObjStacks.
  	self assert: self allObjectsUnmarked.
  	self runLeakCheckerForFullGC: true!

Item was changed:
  ----- Method: SpurMemoryManager>>markAndTrace: (in category 'gc - global') -----
  markAndTrace: objOop
  	"Mark the argument, and all objects reachable from it, and any remaining objects on the mark stack.
  	 Follow forwarding pointers in the scan."
  	| objToScan index field |
  	self assert: (self isNonImmediate: objOop).
  	"if markAndTrace: is to follow and eliminate forwarding pointers
  	 in its scan it cannot be handed an r-value which is forwarded."
  	self assert: (self isForwarded: objOop) not.
  	(self isMarked: objOop) ifTrue:
  		[^self].
  	"self setIsMarkedOf: objOop to: false" "for debugging"
  	self setIsMarkedOf: objOop to: true.
  
  	"Now scan the object, and any remaining objects on the mark stack."
  	objToScan := objOop.
  	"To avoid overflowing the mark stack when we encounter large objects, we
  	 push the obj, then its numStrongSlots, and then index the object from the stack."
  	[| numStrongSlots |
  	 ((self isImmediate: objToScan)
  	 or: [numStrongSlots := self numStrongSlotsOf: objToScan ephemeronInactiveIf: #inactiveOrFailedToDeferScan:.
  		 numStrongSlots > self traceImmediatelySlotLimit])
  		ifTrue: "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
  			[(self isImmediate: objToScan)
  				ifTrue:
  					[index := self integerValueOf: objToScan.
  					 objToScan := self topOfObjStack: markStack]
  				ifFalse:
  					[index := numStrongSlots].
  			 [index > 0] whileTrue:
  				[index := index - 1.
  				 field := self fetchPointer: index ofObject: objToScan.
  				 (self isOopForwarded: field) ifTrue:
  					[field := self followForwarded: field.
  					 self storePointerUnchecked: index ofObject: objToScan withValue: field].
  				 ((self isImmediate: field)
  				  or: [self isMarked: field]) ifFalse:
  					[self setIsMarkedOf: field to: true.
+ 					 (self isWeakNonImm: field)
- 					 (self isWeakNonImm: objToScan)
  						ifTrue: [self push: field onObjStack: weaklingStack]
  						ifFalse:
+ 							[index > 0 ifTrue:
+ 								[(self topOfObjStack: markStack) ~= objToScan ifTrue: 
+ 									[self push: objToScan onObjStack: markStack].
+ 								 self push: (self integerObjectOf: index) onObjStack: markStack.
+ 								 objToScan := field.
+ 								 index := -1]]]].
- 							[(self topOfObjStack: markStack) ~= objToScan ifTrue: 
- 								[self push: objToScan onObjStack: markStack].
- 							 self push: (self integerObjectOf: index) onObjStack: markStack].
- 					 objToScan := field.
- 					 index := -1]].
  			 index >= 0 ifTrue: "if loop terminated without finding an unmarked referent, switch to top of stack."
  				[objToScan := self popObjStack: markStack.
  				 objToScan = objOop ifTrue:
  					[objToScan := self popObjStack: markStack]]]
  		ifFalse: "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
  			[index := numStrongSlots.
  			 [index > 0] whileTrue:
  				[index := index - 1.
  				 field := self fetchPointer: index ofObject: objToScan.
  				 (self isOopForwarded: field) ifTrue:
  					[field := self followForwarded: field.
  					 self storePointerUnchecked: index ofObject: objToScan withValue: field].
  				 ((self isImmediate: field)
  				  or: [self isMarked: field]) ifFalse:
  					[self setIsMarkedOf: field to: true.
  					 (self isWeakNonImm: field)
  						ifTrue: [self push: field onObjStack: weaklingStack]
  						ifFalse:
  							[self push: field onObjStack: markStack.
  							 numStrongSlots := self numStrongSlotsOf: field ephemeronInactiveIf: #inactiveOrFailedToDeferScan:.
  							 numStrongSlots > self traceImmediatelySlotLimit ifTrue:
  								[self push: (self integerObjectOf: numStrongSlots) onObjStack: markStack]]]].
  			 objToScan := self popObjStack: markStack].
  	 objToScan notNil] whileTrue!

Item was changed:
  ----- Method: SpurMemoryManager>>postBecomeOrCompactScanClassTable: (in category 'become implementation') -----
  postBecomeOrCompactScanClassTable: effectsFlags
  	"Scan the class table post-become (iff a pointer object or compiled method was becommed),
  	 or post-compact.
  	 Note that one-way become can cause duplications in the class table.
  	 When can these be eliminated?  We use the classTableBitmap to mark classTable entries
  	 (not the classes themselves, since marking a class doesn't help in knowing if its index is used).
  	 On image load, and during incrememtal scan-mark and full GC, classIndices are marked.
  	 We can somehow avoid following classes from the classTable until after this mark phase."
  	self assert: self validClassTableRootPages.
  
  	(effectsFlags anyMask: BecamePointerObjectFlag+BecameCompiledMethodFlag) ifFalse: [^self].
  	
  	0 to: numClassTablePages - 1 do:
  		[:i| | page |
  		page := self fetchPointer: i ofObject: hiddenRootsObj.
+ 		self assert: (self isForwarded: page) not.
  		0 to: (self numSlotsOf: page) - 1 do:
  			[:j| | classOrNil |
  			classOrNil := self fetchPointer: j ofObject: page.
  			classOrNil ~= nilObj ifTrue:
  				[(self isForwarded: classOrNil) ifTrue:
  					[classOrNil := self followForwarded: classOrNil.
  					 self storePointer: j ofObject: page withValue: classOrNil].
  				 self scanClassPostBecome: classOrNil effects: effectsFlags]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>postCompactScanClassTable (in category 'become implementation') -----
  postCompactScanClassTable
  	"Scan the class table post-compact.  Ensure all pages and
  	 all classes are not forwarded."
  
  	0 to: numClassTablePages - 1 do:
  		[:i| | page |
  		page := self fetchPointer: i ofObject: hiddenRootsObj.
  		(self isForwarded: page) ifTrue: "this check is for eliminateAndFreeForwarders"
  			[page := self followForwarded: page.
  			 self storePointer: i ofObject: hiddenRootsObj withValue: page]].
  	self assert: self validClassTableRootPages.	
+ 	self postBecomeOrCompactScanClassTable: BecamePointerObjectFlag+BecameCompiledMethodFlag!
- 	self postBecomeOrCompactScanClassTable: BecamePointerObjectFlag!



More information about the Vm-dev mailing list