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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 15 17:04:44 UTC 2013


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

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

Name: VMMaker.oscog-eem.459
Author: eem
Time: 15 October 2013, 10:01:56.071 am
UUID: d2ffc89b-e4ff-4404-902d-bc687cf089b6
Ancestors: VMMaker.oscog-eem.458

Add extraRoots and implement doBecome:to:copyHash:.

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

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeLoop (in category 'scavenger') -----
  scavengeLoop
  	"This is the inner loop of the main routine, scavenge.  It first scavenges the new objects immediately
  	 reachable from old ones. Then it scavenges those that are transitively reachable.  If this results in a
  	 promotion, the promotee gets remembered, and it first scavenges objects adjacent to the promotee,
  	 then scavenges the ones reachable from the promoted.  This loop continues until no more reachable
  	 objects are left.  At that point, pastSurvivorSpace is exchanged with futureSurvivorSpace.
  
  	 Notice that each pointer in a live object is inspected once and only once.  The previousRememberedSetSize
  	 and previousFutureSurvivorSpaceLimit variables ensure that no object is scanned twice, as well as
  	 detecting closure.  If this were not true, some pointers might get forwarded twice.
  
  	 An extension of the algorithm presented in David's original paper is to handle weak arrays and ephemerons.
  	 Weak arrays should not have their weak referents scavenged unless there are strong references to them.
  	 Ephemerons should fire if their key is not reachable other than from ephemerons and weak arrays.
  	 Handle this by maintaining a list for weak arrays and a list for ephemerons, which allow scavenging these
  	 objects once all other objects in new space have been scavenged, hence allowing the scavenger to
  	 detect which referents in new space of weak arrays are dead and of ephemeron keys are only live due to
  	 ephemerons.  Read the class comment for a more in-depth description of the algorithm."
  
  	| previousFutureSurvivorStart firstTime |
  	self assert: futureSurvivorStart = futureSpace start. "future space should be empty at the start"
  
  	weakList := ephemeronList := nil.
  	numRememberedEphemerons := 0.
  	firstTime := true.
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorStart := futureSurvivorStart.
  
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
  	 previousRememberedSetSize := rememberedSetSize.
  	 firstTime ifTrue:
  		[coInterpreter mapInterpreterOops.
+ 		 manager mapExtraRoots.
  		 firstTime := false].
  	 "if nothing more copied and forwarded (or remembered by mapInterpreterOops)
  	  to scavenge, and no ephemerons to process, scavenge is done."
  	 (previousRememberedSetSize = rememberedSetSize
  	  and: [previousFutureSurvivorStart = futureSurvivorStart
  	  and: [numRememberedEphemerons = 0
  	  and: [ephemeronList isNil]]]) ifTrue:
  		[^self].
  
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorStart.
  	 previousFutureSurvivorStart := futureSurvivorStart.
  
  	 "no more roots created to scavenge..."
  	 previousRememberedSetSize = rememberedSetSize ifTrue:
  		[(numRememberedEphemerons = 0
  		  and: [ephemeronList isNil]) ifTrue:
  			[^self]. "no ephemerons to process, scavenge is done."
  
  		 "all reachable objects in this cycle have been promoted to futureSpace.
  		  ephemerons can now be processed."
  		 self processEphemerons]] repeat!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	self declareCAsOop: #(memory freeStart scavengeThreshold newSpaceLimit lowSpaceThreshold freeOldSpaceStart endOfMemory sortedFreeChunks)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs'])
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #freeLists declareC: #'sqInt *freeLists'.
  	aCCodeGenerator
  		var: #remapBuffer
+ 		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
+ 	aCCodeGenerator
+ 		var: #extraRoots
+ 		declareC: 'sqInt* extraRoots[ExtraRootSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'.!
- 		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'!

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
  	"CogObjectMemory initialize"
  	CheckObjectOverwrite := true.
  
  	"The remap buffer support is for compatibility; Spur doesn't GC during allocation.
  	 Eventually this should die."
+ 	RemapBufferSize := 25.
+ 
+ 	"Extra roots are for plugin support."
+ 	ExtraRootsSize := 2048 "max. # of external roots"!
- 	RemapBufferSize := 25!

Item was added:
+ ----- Method: SpurMemoryManager>>addGCRoot: (in category 'plugin support') -----
+ addGCRoot: varLoc
+ 	"Add the given variable location to the extra roots table."
+ 	<api>
+ 	<var: #varLoc type: #'sqInt *'>
+ 	extraRootCount >= ExtraRootsSize ifTrue: [^false]. "out of space"
+ 	extraRoots at: (extraRootCount := extraRootCount + 1) put: varLoc.
+ 	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity (in category 'debug support') -----
  checkHeapIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| prevObj prevPrevObj ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		(self isFreeObject: obj) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
  				 (scavenger isInRememberedSet: obj) ifFalse:
  					[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  					 self eek.
  					 ok := false]].
  			 (self isForwarded: obj)
  				ifTrue:
  					[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  					 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  						 self eek.
  						 ok := false].
  					 (self isYoung: fieldOop) ifTrue:
  						[containsYoung := true]]
  				ifFalse:
  					[classOop := self classAtIndex: (classIndex := self classIndexOf: obj).
  					 ((classOop isNil or: [classOop = nilObj])
  					  and: [obj ~= self freeListsObject]) ifTrue:
  						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  						 self eek.
  						 ok := false].
  					 self baseHeaderSize to: (self lastPointerOf: obj) by: BytesPerOop do:
  						[:ptr|
  						 fieldOop := self longAt: obj + ptr.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[| fi |
  							 fi := ptr - self baseHeaderSize / self wordSize.
  							 (fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
  									[coInterpreter print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false].
  									 "don't be misled by CogMethods; they appear to be young, but they're not"
  									 ((self isYoung: fieldOop) and: [fieldOop >= startOfMemory]) ifTrue:
  										[containsYoung := true]]]]].
  					(containsYoung and: [(self isYoung: obj) not]) ifTrue:
  						[(self isRemembered: obj) ifFalse:
  							[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  							 self eek.
  							 ok := false]]].
  		prevPrevObj := prevObj.
  		prevObj := obj].
  	numRememberedRootsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedRootsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
+ 				[coInterpreter print: 'misaligned oop in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
- 				[coInterpreter print: 'misaligned oop in rootTable @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
+ 	1 to: remapBufferCount do:
+ 		[:ri| | obj |
- 	self flag: 'no support for remap buffer yet'.
- 	"1 to: remapBufferCount do:
- 		[:ri|
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
+ 				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
+ 					[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
+ 					 self eek.
+ 					 ok := false]]].
+ 	1 to: extraRootCount do:
+ 		[:ri| | obj |
- 				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
- 					ifTrue:
- 						[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 						 self eek.
- 						 ok := false]]]."
- 	self flag: 'no support for extraRoots yet'.
- 	"1 to: extraRootCount do:
- 		[:ri|
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
+ 				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
+ 					[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
+ 					 self eek.
+ 					 ok := false]]].
- 				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
- 					ifTrue:
- 						[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
- 						 self eek.
- 						 ok := false]]]."
  	^ok!

Item was added:
+ ----- Method: SpurMemoryManager>>doBecome:to:copyHash: (in category 'become implementation') -----
+ doBecome: obj1 to: obj2 copyHash: copyHashFlag
+ 	| hashBits |
+ 	self forward: obj1 to: obj2.
+ 	copyHashFlag ifTrue:
+ 		[hashBits := self rawHashBitsOf: obj2.
+ 		 "silently refuse to change the hash of classes; this shouldn't happen anyway."
+ 		 (self classAtIndex: hashBits) ~= obj2 ifTrue:
+ 			[hashBits := self rawHashBitsOf: obj1.
+ 			 self setHashBitsOf: obj2 to: hashBits]]!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
+ 	remapBufferCount := extraRoots := 0. "see below"
- 	remapBufferCount := 0.
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := scavengeInProgress := false.
  	becomeEffectsFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statGCEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := statTenures := statSurvivorCount := 0.
  	statRootTableOverflows := statSweepCount := statMarkCount := statSpecialMarkCount := statMkFwdCount := 0.
  	self flag: #temporary.
  	shrinkThreshold := 16r10000000. "something huge for now"
  
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavengerSimulator new manager: self; yourself.
  	segmentManager := SpurSegmentManager new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
+ 	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new].
+ 
+ 	"N.B. We *don't* initialize extraRoots because we don't simulate it."!
- 	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new]!

Item was added:
+ ----- Method: SpurMemoryManager>>mapExtraRoots (in category 'garbage collection') -----
+ mapExtraRoots
+ 	self assert: remapBufferCount = 0.
+ 	1 to: extraRootCount do:
+ 		[:i | | oop |
+ 		oop := (extraRoots at: i) at: 0.
+ 		((self isImmediateObject: oop) or: [self isFreeObject: oop]) ifFalse:
+ 			[(self shouldRemapObj: oop) ifTrue:
+ 				[(extraRoots at: i) at: 0 put: (self remapObj: oop)]]]!

Item was added:
+ ----- Method: SpurMemoryManager>>removeGCRoot: (in category 'plugin support') -----
+ removeGCRoot: varLoc
+ 	"Remove the given variable location to the extra roots table."
+ 	<api>
+ 	<var: #varLoc type: #'sqInt *'>
+ 	1 to: extraRootCount do:
+ 		[:i|
+ 		varLoc = (extraRoots at: i) ifTrue: "swap varLoc with last entry"
+ 			[extraRoots at: i put: (extraRoots at: extraRootCount).
+ 			 extraRootCount := extraRootCount - 1.
+ 			 ^true]].
+ 	^false "not found"!



More information about the Vm-dev mailing list