[Vm-dev] VM Maker: VMMaker.oscog.seperateMarking-WoC.3251.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 9 23:27:05 UTC 2022


Tom Braun uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog.seperateMarking-WoC.3251.mcz

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

Name: VMMaker.oscog.seperateMarking-WoC.3251
Author: WoC
Time: 10 August 2022, 1:26:34.109382 am
UUID: 6e093abb-8fd3-4df3-b8f2-877c400b96d0
Ancestors: VMMaker.oscog.seperateMarking-WoC.3250

mark ephemeronStack
insert some additional checks
use write barrier only when marking

=============== Diff against VMMaker.oscog.seperateMarking-WoC.3250 ===============

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
+ SystemOrganization addCategory: #'VMMaker-SpurGarbageCollector'!
+ SystemOrganization addCategory: #'VMMaker-SpurGarbageCollectorSimulation'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
- SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Utilities'!
+ SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!
- SystemOrganization addCategory: #'VMMaker-SpurGarbageCollectorSimulation'!
- SystemOrganization addCategory: #'VMMaker-SpurGarbageCollector'!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>setIsGreyOf:to: (in category 'header access') -----
  setIsGreyOf: objOop to: aBoolean
  	"objOop = 16rB26020 ifTrue: [self halt]."
  	"(#(16r1971D0 16r196EE0 16r197048 16r197148) includes: objOop) ifTrue:
  		[self halt]."
  	GCEventLog register: ((aBoolean
  		ifTrue: [GCGreyEvent]
  		ifFalse: [GCUngreyEvent]) address: objOop).
- 		
- 	objOop = 16r448 ifTrue: [self halt].
  
  	super setIsGreyOf: objOop to: 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]"!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector>>doIncrementalCollect (in category 'as yet unclassified') -----
+ doIncrementalCollect
+ 
+ 	phase = InMarkingPhase
+ 		ifTrue: [
+ 			marker incrementalMarkObjects
+ 				ifTrue: [
+ 					"manager allPastSpaceObjectsDo: [:obj | self assert: (manager isWhite: obj)]."
+ 					manager runLeakCheckerFor: GCModeFull.
+ 					
+ 					"when sweeping the mutator needs to allocate new objects black as we do not have any information about them.
+ 					We only know if they should get swept after the next marking -> keep them alive for this cycle"
+ 					self allocatorShouldAllocateBlack: true.
+ 					phase := InSweepingPhase.
+ 					
+ 					"marking is done and thus all forwarding references are resolved -> we can use the now free segments that were 
+ 					compacted during the last cycle"
+ 					compactor freePastSegmentsAndSetSegmentToFill.
+ 					
+ 					^ self]
+ 				ifFalse: [manager runLeakCheckerFor: GCModeIncremental]].
+ 		
+ 	phase = InSweepingPhase
+ 		ifTrue: [
+ 			compactor incrementalSweep
+ 				ifTrue: [
+ 					self allocatorShouldAllocateBlack: false.
+ 					manager allOldSpaceObjectsDo: [:ea | self assert: (manager isWhite: ea) ].
+ 					"self assert: manager allObjectsUnmarked."
+ 					phase := InCompactingPhase.
+ 					^ self]].
+ 		
+ 	phase = InCompactingPhase
+ 		ifTrue: [
+ 			compactor incrementalCompact
+ 				ifTrue: [phase := InMarkingPhase.
+ 					^ self]]!

Item was changed:
  ----- Method: SpurIncrementalGarbageCollector>>incrementalCollect (in category 'as yet unclassified') -----
  incrementalCollect
  
+ 	self doIncrementalCollect.
+ 	
+ 	self assert: manager validObjStacks.!
- 	phase = InMarkingPhase
- 		ifTrue: [
- 			marker incrementalMarkObjects
- 				ifTrue: [
- 					"manager allPastSpaceObjectsDo: [:obj | self assert: (manager isWhite: obj)]."
- 					
- 					"when sweeping the mutator needs to allocate new objects black as we do not have any information about them.
- 					We only know if they should get swept after the next marking -> keep them alive for this cycle"
- 					self allocatorShouldAllocateBlack: true.
- 					phase := InSweepingPhase.
- 					
- 					"marking is done and thus all forwarding references are resolved -> we can use the now free segments that were 
- 					compacted during the last cycle"
- 					compactor freePastSegmentsAndSetSegmentToFill.
- 					
- 					^ self]].
- 		
- 	phase = InSweepingPhase
- 		ifTrue: [
- 			compactor incrementalSweep
- 				ifTrue: [
- 					self allocatorShouldAllocateBlack: false.
- 					manager allOldSpaceObjectsDo: [:ea | self assert: (manager isWhite: ea) ].
- 					"self assert: manager allObjectsUnmarked."
- 					phase := InCompactingPhase.
- 					^ self]].
- 		
- 	phase = InCompactingPhase
- 		ifTrue: [
- 			compactor incrementalCompact
- 				ifTrue: [phase := InMarkingPhase.
- 					^ self]]!

Item was changed:
  ----- Method: SpurIncrementalMarker>>incrementalMarkObjects (in category 'marking - incremental') -----
  incrementalMarkObjects
  	"this method is to be run directly after a scavenge -> we can assume there are ony objects in the now past survivor space"
  
  	<inline: #never> "for profiling"
  	
  	"manager runLeakCheckerFor: GCModeIncremental."
  	
  	self initializeForNewMarkingPassIfNecessary.
  
  	[ | continueMarking |
  	(manager isEmptyObjStack: manager markStack)
  		ifTrue: [self pushAllRootsOnMarkStack.
  			" manager sizeOfObjStack: manager markStack.
  			did we finish marking?"
  			(manager isEmptyObjStack: manager markStack)
  				ifTrue: [self finishMarking.
  					^ true]].
  	
  	
+ 	"due to a slang limitations we have to assign the result into variable => do not remove!!"
- 	"due to a slang limitations we have to assign the result into variable"
  	continueMarking := self incrementalMark.
  	continueMarking] whileTrue.
  
  	^ false
  	!

Item was changed:
  ----- Method: SpurIncrementalMarker>>pushHiddenRootsReferencesOnMarkingStack (in category 'root-scanning') -----
  pushHiddenRootsReferencesOnMarkingStack
  
  	| classTablePageSize |
  	self markAndTraceObjStack: manager markStack andContents: false.
  	self markAndTraceObjStack: manager weaklingStack andContents: false.
  	self markAndTraceObjStack: manager mournQueue andContents: true.
+ 	self markAndTraceObjStack: manager ephemeronStack andContents: true.
  	
  	classTablePageSize := manager numStrongSlotsOfInephemeral: manager classTableFirstPage.
  	self markNSlots: classTablePageSize of: manager classTableFirstPage.
  	self blackenObject: manager classTableFirstPage!

Item was changed:
  ----- Method: SpurIncrementalMarker>>writeBarrierFor:at:with: (in category 'barrier') -----
  writeBarrierFor: anObject at: index with: value
  	"a dijkstra style write barrier with the addition of the generation check
  	objects that are not able to contain pointers are ignored too, as the write barries
  	should ensure we lose no references and this objects do not hold any of them"
  	<inline: true>
  	
  	self flag: #Todo. "we probably want the oldObject check to be the first one as it is only a pointer comparison and no dereferencing is needed"
+ 	(self marking and: [(self isLeafInObjectGraph: anObject) not and: [(manager isOldObject: anObject) and: [manager isMarked: anObject]]])
- 	((self isLeafInObjectGraph: anObject) not and: [(manager isOldObject: anObject) and: [manager isMarked: anObject]])
  		ifTrue: [self pushOnMarkingStackAndMakeGreyIfNecessary: value]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>writeBarrierFor:at:with: (in category 'as yet unclassified') -----
+ writeBarrierFor: anObject at: index with: value
+ 
+ 	GCEventLog
+ 		inContext: #writeBarrier 
+ 		do: [super writeBarrierFor: anObject at: index with: value]
+ 	!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>canUseAsFreeSpace: (in category 'as yet unclassified') -----
+ canUseAsFreeSpace: objOop
+ 
+ 	"objOop = 16r25FDBD8 ifTrue: [self halt]."
+ 	^ super  canUseAsFreeSpace: objOop!



More information about the Vm-dev mailing list