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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 23 05:46:15 UTC 2020


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

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

Name: VMMaker.oscog-eem.2894
Author: eem
Time: 22 November 2020, 9:46:07.518953 pm
UUID: 6c77c06e-a17e-4dcf-85d9-90943dd5eae8
Ancestors: VMMaker.oscog-eem.2893

MTVM:
Separate from MultiProcessor.  Have CogThreadManager>>releaseVM & tryLockVMOwnerTo: simulate thread switches, since these are effectively the only places they occur in this simple threading scheme.  The full complexity of MultiProcessor isn't needed.

To make this work change all senders of tryLockVMOwnerTo: to invoke CogThreadManager's simulation-only wrapper around Cogit>>tryLockVMOwnerTo:.

Simplify and correct checks and initialization of the processor's thread-specific stack pointers.

Provide a multi-threaded version of primtRumpCStack that prints the individual stacks for active threads.

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

Item was changed:
  ----- Method: CoInterpreter>>assertValidExternalStackPointers (in category 'debug support') -----
  assertValidExternalStackPointers
+ 	<doNotGenerate>
  	"For use *ONLY* by routines coming in to the VM,
+ 	 i.e. handleCallOrJumpSimulationTrap:.  This is because it nils localFP as a side-effect,
+ 	 and it does so so that the head frame can be determined reliably."
- 	 i.e. handleCallOrJumpSimulationTrap:.  This is because it nils localFP as a side-effect."
  	self assert: framePointer < stackPage baseAddress.
  	self assert: stackPointer < framePointer.
  	self assert: framePointer > stackPointer.
  	self assert: stackPointer >= (stackPage realStackLimit - self stackLimitOffset).
  	localFP := nil!

Item was removed:
- ----- Method: CoInterpreter>>setFramePointer:stackPointer:for: (in category 'initialization') -----
- setFramePointer: cFramePointer stackPointer: cStackPointer for: processor
- 	<doNotGenerate>
- 	processor
- 		setFramePointer: (self setCFramePointer: cFramePointer)
- 		stackPointer: (self setCStackPointer: cStackPointer)!

Item was changed:
  ----- Method: CoInterpreterMT>>assertCStackPointersBelongToCurrentThread (in category 'simulation') -----
  assertCStackPointersBelongToCurrentThread
+ 	<cmacro: '(ignored) 0'> "simulation only"
- 	<cmacro: '() 0'> "simulation only"
  	| ownerIndex range |
  	self assert: (ownerIndex := cogThreadManager getVMOwner) > 0.
+ 	range := self cStackRangeForThreadIndex: ownerIndex.
+ 	self assert: ((range includes: CFramePointer) and: [range includes: CStackPointer])!
- 	self assert: ((range := self cStackRangeForThreadIndex: ownerIndex) includes: CFramePointer).
- 	self assert: (range includes: CStackPointer)!

Item was added:
+ ----- Method: CoInterpreterMT>>assertProcessorStackPointersBelongToCurrentThread (in category 'simulation') -----
+ assertProcessorStackPointersBelongToCurrentThread
+ 	<cmacro: '(ignored) 0'> "simulation only"
+ 	| ownerIndex range |
+ 	self assert: (ownerIndex := cogThreadManager getVMOwner) > 0.
+ 	range := self cStackRangeForThreadIndex: ownerIndex.
+ 	self assert: ((range includes: cogit processor fp) and: [range includes: cogit processor sp])!

Item was changed:
  ----- Method: CoInterpreterMT>>enterSmalltalkExecutiveImplementation (in category 'initialization') -----
  enterSmalltalkExecutiveImplementation
  	"Main entry-point into the interpreter at each execution level, where an execution
  	 level is either the start of execution or reentry for a callback.  Capture the C stack
  	 pointers so that calls from machine-code into the C run-time occur at this level.
  	 This is the actual implementation, separated from enterSmalltalkExecutive so the
  	 simulator can wrap it in an exception handler and hence simulate the setjmp/longjmp.
  
  	 Override to return if a longjmp to reenterInterpreter passes a parameter greater than 1.
  	 This causes a return to threadSchedulingLoop:startingVM: and is used to surrender
  	 control to another thread."
  	<inline: false>
  	self assertSaneThreadAndProcess.
+ 	self assertProcessorStackPointersBelongToCurrentThread. "At this point CFramePointer/CStackPointer have yet to be assigned".
  	^super enterSmalltalkExecutiveImplementation!

Item was changed:
  ----- Method: CoInterpreterMT>>returnToSchedulingLoopAndReleaseVMOrWakeThread:source: (in category 'process primitive support') -----
  returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: source
  	<var: #vmThread type: #'CogVMThread *'>
  	<inline: false>
- 	self cCode:
- 			[self flag: 'this is just for debugging.  Note the current C stack pointers'.
- 			 cogThreadManager currentVMThread
- 				cStackPointer: CStackPointer;
- 				cFramePointer: CFramePointer]
- 		inSmalltalk:
- 			[| range | range := self cStackRangeForThreadIndex: cogThreadManager getVMOwner.
- 			 self assert: ((range includes: CStackPointer) and: [range includes: CFramePointer])].
  	self recordThreadSwitchTo: (vmThread ifNotNil: [vmThread index] ifNil: [0]) source: source.
  	vmThread
  		ifNotNil: [cogThreadManager wakeVMThreadFor: vmThread index]
  		ifNil: [cogThreadManager releaseVM].
  	"I am not frightened of flying.
  	 Any value will do.  I don't mind.
  	 Why should I be frightened of flying?
  	 There's no reason for it."
  	self _longjmp: reenterThreadSchedulingLoop _: 1 !

Item was removed:
- ----- Method: CoInterpreterMT>>setFramePointer:stackPointer:for: (in category 'initialization') -----
- setFramePointer: cFramePointer stackPointer: cStackPointer for: processor
- 	<doNotGenerate>
- 	self flag: #design.
- 	CFramePointer ifNil:
- 		[self setCFramePointer: cFramePointer; setCStackPointer: cStackPointer].
- 	processor
- 		setFramePointer: cFramePointer
- 		stackPointer: cStackPointer!

Item was changed:
  ----- Method: CoInterpreterMT>>threadSchedulingLoop: (in category 'vm scheduling') -----
  threadSchedulingLoop: vmThread
  	"Enter a loop attempting to run the VM with the highest priority process and
  	 blocking on the thread's OS semaphore when unable to run that process.
  	 This version is for simulation only, simulating the longjmp back to the real
  	 threadSchedulingLoopImplementation: through exception handling."
  
  	<cmacro: '(vmThread) threadSchedulingLoopImplementation(vmThread)'>
+ 	cogit initializeProcessorStack: (self cStackRangeForThreadIndex: vmThread index) last.
- 	self initializeProcessorForThreadIndex: vmThread index.
  	[[self threadSchedulingLoopImplementation: vmThread]
  		on: ReenterThreadSchedulingLoop
  		do: [:ex| self assert: ex returnValue = 1. ex return: true]] whileTrue!

Item was added:
+ ----- Method: CogThreadManager>>ensureInitializedProcessor:forThreadIndex: (in category 'simulation') -----
+ ensureInitializedProcessor: aProcessor forThreadIndex: threadIndex
+ 	"Ensure aProcessor has stack pointers within its defined range, initializing it if not."
+ 	<doNotGenerate>
+ 	| range |
+ 	range := coInterpreter cStackRangeForThreadIndex: threadIndex.
+ 	self assert: (range includes: aProcessor fp) = (range includes: aProcessor sp).
+ 	((range includes: aProcessor fp) and: [range includes: aProcessor sp]) ifFalse:
+ 		[aProcessor smashCallerSavedRegistersWithValuesFrom: 16r90000000 by: coInterpreter objectMemory wordSize / 2.
+ 		 cogit initializeProcessorStack: range last]!

Item was changed:
  ----- Method: CogThreadManager>>releaseVM (in category 'public api') -----
  releaseVM
+ 	"In the simulation this is where register state is saved; it is switched in tryLockVMOwnerTo:."
+ 	self cCode: [] inSmalltalk:
+ 		[vmOwner ~= 0 ifTrue:
+ 			[registerStates at: vmOwner put: cogit processor registerState]].
  	self setVMOwner: 0!

Item was added:
+ ----- Method: CogThreadManager>>threadsDo: (in category 'simulation') -----
+ threadsDo: aBlock
+ 	1 to: numThreads do:
+ 		[:i|
+ 		(threads at: i) ifNotNil:
+ 			[:thread| aBlock value: thread]]!

Item was changed:
  ----- Method: CogThreadManager>>tryLockVMOwnerTo: (in category 'simulation') -----
+ tryLockVMOwnerTo: threadIndex
- tryLockVMOwnerTo: value
  	"In the real VM this is a direct call of Cogit>>#tryLockVMOwnerTo:/ceTryLockVMOwner.
+ 	 In the simulation this is where register state is saved and switched, simulaitng a thread switch.
+ 	 releaseVM also saves register state.  The code here and in registerState allow us to avoid the
+ 	 expensive and complex MultiProcessor hack."
- 	 In the simulation this is where we save and switch register state."
  	<doNotGenerate>
+ 	| prior processor result |
+ 	self deny: threadIndex = 0.
- 	| current post prior processor |
  	processor := cogit processor.
  	prior := processor registerState.
+ 	"A thread switch would (have) occur(ed) if it were that the VM were owned other than by threadIndex"
+ 	vmOwner ~= threadIndex ifTrue:
+ 		[vmOwner ~= 0 ifTrue:
+ 			[registerStates at: vmOwner put: prior].
+ 		 processor setRegisterState: (registerStates
+ 										at: threadIndex
+ 										ifAbsentPut:
+ 											[self ensureInitializedProcessor: processor forThreadIndex: threadIndex.
+ 											 processor registerState])].
+ 	result := cogit tryLockVMOwnerTo: threadIndex.
+ 	self assert: result = (threadIndex = vmOwner).
+ 	registerStates at: threadIndex put: processor registerState.
+ 	threadIndex ~= vmOwner ifTrue: "the lock attempt failed; undo the (processor) thread switch."
+ 		[processor setRegisterState: prior].
+ 	^result!
- 	vmOwner ~= 0 ifTrue:
- 		[registerStates at: vmOwner put: prior].
- 	(cogit tryLockVMOwnerTo: value) ifFalse:
- 		[^false].
- 	post := processor registerState.
- 	current := registerStates
- 					at: vmOwner
- 					ifAbsentPut:
- 						[self assert: vmOwner = value.
- 						 processor voidRegisterState; registerState].
- 	1 to: prior size do:
- 		[:i| | neuf |
- 		(prior at: i) ~= (neuf := post at: i) ifTrue:
- 			[current at: i put: neuf]].
- 	cogit processor setRegisterState: current.
- 	^true!

Item was changed:
  ----- Method: CogVMSimulator>>ownVM: (in category 'debugging traps') -----
  ownVM: threadIndexAndFlags
  	"This method includes or excludes CoInterpreterMT methods as required.
  	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 	"(threadIndexAndFlags anyMask: DisownVMForProcessorRelinquish << DisownFlagsShift) ifFalse:
+ 		[self break]."
- 	(threadIndexAndFlags anyMask: DisownVMForProcessorRelinquish << DisownFlagsShift) ifFalse:
- 		[self break].
  	^self perform: #ownVM:
  		withArguments: {threadIndexAndFlags}
  		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was changed:
  ----- Method: CogVMSimulator>>printRumpCStack (in category 'rump c stack') -----
  printRumpCStack
+ 	cogThreadManager ifNil:
+ 		[^self printRumpCStackTo: heapBase - objectMemory wordSize].
+ 	cogThreadManager threadsDo:
+ 		[:thread| self printRumpCStackForThread: thread]!
- 	self printRumpCStackTo: heapBase - objectMemory wordSize!

Item was added:
+ ----- Method: CogVMSimulator>>printRumpCStackForThread: (in category 'rump c stack') -----
+ printRumpCStackForThread: thread
+ 	| range start coldTop |
+ 	range := self cStackRangeForThreadIndex: thread index.
+ 	start := range first bitClear: objectMemory tagMask.
+ 	coldTop := range last.
+ 	[start < coldTop and: [(objectMemory longAt: start) = 0]] whileTrue:
+ 		[start := start + objectMemory wordSize].
+ 	(start = coldTop and: [(objectMemory longAt: start) = 0]) ifTrue:
+ 		[^self].
+ 	start := start - (2 * objectMemory wordSize) max: range start.
+ 	transcript nextPutAll: 'thread '; print: thread index; cr.
+ 	self printRumpCStackFrom: start to: coldTop cfp: thread cFramePointer csp: thread cStackPointer.
+ 	range first < start ifTrue:
+ 		[self print: 'zeros...'; cr]!

Item was added:
+ ----- Method: CogVMSimulator>>printRumpCStackFrom:to:cfp:csp: (in category 'rump c stack') -----
+ printRumpCStackFrom: start to: address cfp: cfp csp: csp
+ 	address
+ 		to: start
+ 		by: objectMemory wordSize negated
+ 		do: [:addr| | label |
+ 			self printHex: addr.
+ 			addr = cogit processor sp ifTrue: [label := ' sp'].
+ 			addr = cogit processor fp ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'fp'].
+ 			addr = csp ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'CSP'].
+ 			addr = cfp ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'CFP'].
+ 			label ifNil: [self tab] ifNotNil: [self print: ' ', label, '->'].
+ 			self tab; printHex: (objectMemory longAt: addr); cr]!

Item was changed:
  ----- Method: CogVMSimulator>>printRumpCStackTo: (in category 'rump c stack') -----
  printRumpCStackTo: address
  	| start |
  	self assert: (self isOnRumpCStack: address).
  	start := heapBase - self rumpCStackSize.
  	[start < address and: [(objectMemory longAt: start) = 0]] whileTrue:
  		[start := start + objectMemory wordSize].
  	start := start - (3 * objectMemory wordSize) max: heapBase - self rumpCStackSize.
+ 	self printRumpCStackFrom: start to: address cfp: CFramePointer csp: CStackPointer.
- 	address
- 		to: start
- 		by: objectMemory wordSize negated
- 		do: [:addr| | label |
- 			self printHex: addr.
- 			addr = cogit processor sp ifTrue: [label := ' sp'].
- 			addr = cogit processor fp ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'fp'].
- 			addr = CStackPointer ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'CSP'].
- 			addr = CFramePointer ifTrue: [label := (label ifNil: [''] ifNotNil: [label, ',']), 'CFP'].
- 			label ifNil: [self tab] ifNotNil: [self print: ' ', label, '->'].
- 			self tab; printHex: (objectMemory longAt: addr); cr].
  	heapBase - self rumpCStackSize < start ifTrue:
  		[self print: 'zeros...'; cr]!

Item was removed:
- ----- Method: CogVMSimulator>>setFramePointer:stackPointer:for: (in category 'multi-threading simulation switch') -----
- setFramePointer: cFramePointer stackPointer: cStackPointer for: processor
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
- 	^self perform: #setFramePointer:stackPointer:for:
- 		withArguments: {cFramePointer. cStackPointer. processor}
- 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was changed:
  ----- Method: Cogit>>ceCaptureCStackPointers (in category 'jit - api') -----
  ceCaptureCStackPointers
  	<api: 'extern void (*ceCaptureCStackPointers)()'>
  	<doNotGenerate>
- 	| range |
  	coInterpreter isCurrentImageFacade ifTrue:
  		[^self].
  	self simulateLeafCallOf: ceCaptureCStackPointers.
  	thisContext sender selector == #generateStackPointerCapture ifTrue:
  		[^self].
  	coInterpreter isThreadedVM ifTrue:
+ 		[coInterpreter assertProcessorStackPointersBelongToCurrentThread]!
- 		[range := coInterpreter cStackRangeForThreadIndex: coInterpreter threadManager getVMOwner.
- 		 self assert: (range notNil "VM is owned"
- 					and: [(range includes: coInterpreter getCFramePointer)
- 					and: [range includes: coInterpreter getCStackPointer]])]!

Item was changed:
  ----- Method: Cogit>>initializeProcessorStack: (in category 'initialization') -----
  initializeProcessorStack: rumpCStackAddress
  	"Initialize the simulation processor's stack pointers, arranging that they are somewhere on the rump C stack."
  	<doNotGenerate>
  	| stackPad cFramePointer cStackPointer |
  	stackPad := 64 max: cStackAlignment.
  	cStackPointer := rumpCStackAddress - stackPad + expectedSPAlignment.
  	cFramePointer := rumpCStackAddress - stackPad + cStackAlignment + expectedFPAlignment.
  	self assert: cStackPointer \\ cStackAlignment = expectedSPAlignment.
  	self assert: cFramePointer \\ cStackAlignment = expectedFPAlignment.
+ 	processor setFramePointer: cFramePointer stackPointer: cStackPointer!
- 	coInterpreter setFramePointer: cFramePointer stackPointer: cStackPointer for: processor!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>setFramePointer:stackPointer:for: (in category 'accessing') -----
- setFramePointer: cFramePointer stackPointer: cStackPointer for: processor
- 	^coInterpreter setFramePointer: cFramePointer stackPointer: cStackPointer for: processor!



More information about the Vm-dev mailing list