[Vm-dev] VM Maker: VMMaker.oscog-cb.2447.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Oct 4 07:41:37 UTC 2018


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2447.mcz

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

Name: VMMaker.oscog-cb.2447
Author: cb
Time: 4 October 2018, 9:41:04.472108 am
UUID: b2f39c11-1d5c-43a9-8925-32eab1591459
Ancestors: VMMaker.oscog-cb.2446

Production VM:
- Fixed a bug in removeSegment: where invalid memory would be accessed when the segment info array was full & a segment removed.

SelectiveCompactor VM:
- Fixed a bug in primitiveResume when a context forwarder is found.
- Fixed SelectiveCompactor postCompaction forwarding logic
-> Just ran SelectiveCompactor with >20Gb workloads without crashes with these fixes.

Might be some redundancy that I need to check in following logic with other code in the VM.

=============== Diff against VMMaker.oscog-cb.2446 ===============

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveResume (in category 'process primitives') -----
  primitiveResume
  	"Put this process on the scheduler's lists thus allowing it to proceed next time there is
  	 a chance for processes of it's priority level.  It must go to the back of its run queue so
  	 as not to preempt any already running processes at this level.  If the process's priority
  	 is higher than the current process, preempt the current process."
  	| proc inInterpreter |
  	proc := self stackTop.  "rcvr"
+ 	(objectMemory isContext: (objectMemory followField: SuspendedContextIndex ofObject: proc)) ifFalse:
- 	(objectMemory isContext: (objectMemory fetchPointer: SuspendedContextIndex ofObject: proc)) ifFalse:
  		[^self primitiveFail].
  	"We're about to switch process, either to an interpreted frame or a
  	 machine code frame. To know whether to return or enter machine code
  	 we have to know from whence we came.  We could have come from the
  	 interpreter, either directly or via a machine code primitive.  We could have
  	 come from machine code.  The instructionPointer tells us where from:"
  	inInterpreter := instructionPointer >= objectMemory startOfMemory.
  	(self resume: proc preemptedYieldingIf: preemptionYields from: CSResume) ifTrue:
  		[self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter]
  
  	"Personally I would like to check MyList, which should not be one of the elements of the scheduler lists.
  	 But there are awful race conditions in things like should:notTakeMoreThan: that mean we can't.
  	 eem 9/27/2010 23:08. e.g.
  
  	| proc myList classLinkedList |
  	proc := self stackTop.
  	myList := objectMemory fetchPointer: MyListIndex ofObject: proc.
  	classLinkedList := self superclassOf: (objectMemory splObj: ClassSemaphore).
  	((self fetchClassOfNonInt: myList) ~= classLinkedList
  	and: [objectMemory isContext: (objectMemory fetchPointer: SuspendedContextIndex ofObject: proc)]) ifFalse:
  		[^self primitiveFail].
  	''We're about to switch process, either to an interpreted frame or a
  	 machine code frame. To know whether to return or enter machine code
  	 we have to know from whence we came.  We could have come from the
  	 interpreter, either directly or via a machine code primitive.  We could have
  	 come from machine code.  The instructionPointer tells us where from:''
  	inInterpreter := instructionPointer >= objectMemory startOfMemory.
  	(self resume: proc  preemptedYieldingIf: preemptionYields from: CSResume) ifTrue:
  		[self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter]"!

Item was added:
+ ----- Method: SpurMemoryManager>>followClassTable (in category 'selective compaction') -----
+ followClassTable
+ 	"In addition to postBecomeScanClassTable:, I follow hiddenRootObj and its pages"
+ 	(self isForwarded: hiddenRootsObj) ifTrue: [hiddenRootsObj := self followForwarded: hiddenRootsObj].
+ 	0 to: numClassTablePages - 1 do:
+ 		[:i| | page |
+ 		page := self followField: i ofObject: hiddenRootsObj.
+ 		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 rawHashBitsOf: classOrNil) = 0 ifTrue:
+ 					[self storePointerUnchecked: j ofObject: page withValue: nilObj.
+ 					 "If the removed class is before the classTableIndex, set the
+ 					  classTableIndex to point to the empty slot so as to reuse it asap."
+ 					 (i << self classTableMajorIndexShift + j) < classTableIndex ifTrue:
+ 						[classTableIndex := i << self classTableMajorIndexShift + j]]]]].
+ 	"classTableIndex must never index the first page, which is reserved for classes known to the VM."
+ 	self assert: classTableIndex >= (1 << self classTableMajorIndexShift).
+ 	self assert: self validClassTableRootPages.!

Item was added:
+ ----- Method: SpurMemoryManager>>followProcessList (in category 'selective compaction') -----
+ followProcessList
+ 	"Eagerly patch all process related forwarders, except suspended contexts which are lazily patched in wakeHighestPriority"
+ 	| scheduler processLists processList proc |
+ 	scheduler := self followField: ValueIndex ofObject: (self splObj: SchedulerAssociation).
+ 	self followField: ActiveProcessIndex ofObject: scheduler.
+ 	processLists := self followField: ProcessListsIndex ofObject: scheduler.
+ 	0 to: (self numSlotsOf: processLists) - 1 do: [:i |
+ 		processList := self followField: i ofObject: processLists.
+ 		self followField: LastLinkIndex ofObject: processList.
+ 		proc := self followField: FirstLinkIndex ofObject: processList.
+ 		[proc = nilObj] whileFalse: [proc := self followField: NextLinkIndex ofObject: proc]].!

Item was changed:
  ----- Method: SpurSegmentManager>>removeSegment: (in category 'growing/shrinking memory') -----
  removeSegment: emptySeg
  	<var: #emptySeg type: #'SpurSegmentInfo *'>
  	| i |
  	i := self indexOfSegment: emptySeg.
  	self assert: i > 0.
  
  	totalHeapSizeIncludingBridges := totalHeapSizeIncludingBridges - emptySeg segSize.
  	manager sqDeallocateMemorySegmentAt: emptySeg segStart asVoidPointer OfSize: emptySeg segSize.
  
+ 	i to: numSegments - 2 do:
- 	i to: numSegments - 1 do:
  		[:j| segments at: j put: (segments at: j + 1)].
  	self cCode: [] inSmalltalk: [segments at: numSegments - 1 put: SpurSegmentInfo new].
  	numSegments := numSegments - 1.
  
  	self bridgeFrom: (self addressOf: (segments at: i - 1))
  		to: (i <= (numSegments - 1) ifTrue: [self addressOf: (segments at: i)]).
  
  	manager setLastSegment: (self addressOf: (segments at: numSegments - 1))!

Item was changed:
  ----- Method: SpurSelectiveCompactor>>postCompactionAction (in category 'compaction') -----
  postCompactionAction
  	| allFlags |
  	"For now we don't optimize and just follow everything everywhere on stack and in caches, let's see in the profiler if we need to optimize with those cases. My guess is that this is < 100 microSecond"
  	manager followSpecialObjectsOop.
  	allFlags := BecamePointerObjectFlag + BecameActiveClassFlag bitOr: BecameCompiledMethodFlag.
+ 	"Note: there is not the OldBecameNewFlag"
+ 	"gcMode flag is cleared after postBecomeAction, reset it."
- 	"should be gcMode Become - gcMode flag is cleared after postBecomeAction"
  	manager coInterpreter postBecomeAction: allFlags.
- 	manager postBecomeScanClassTable: allFlags.
  	manager coInterpreter setGCMode: GCModeFull.
  	
+ 	"Special to selective, crazy objects can be forwarded..."
+ 	"manager postBecomeScanClassTable: allFlags. => Done in followClassTable"
+ 	manager followClassTable.
+ 	manager followProcessList.
+ 	manager followForwardedObjStacks.
+ 	
  	"Not sure the following are needed...
  	coInterpreter mapInterpreterOops.
  	manager mapExtraRoots."
  	self assert: manager validClassTableHashes.!



More information about the Vm-dev mailing list