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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 6 21:25:57 UTC 2021


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

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

Name: VMMaker.oscog-eem.3119
Author: eem
Time: 6 December 2021, 1:25:40.62613 pm
UUID: c0b40a55-50ca-4dd9-8b6f-d355a6dd5e1f
Ancestors: VMMaker.oscog-eem.3118

CoInterpreterMT simulation:
Fix the rump C stack segmentation so that each thread does indeed get its own 4k page of teh rump C stack.

Document what is likely a cul de sac in multi-processor simulation. This version attempts to follow this view of the world:

	On switching osProcess we have to both
		- SAVE old process's register state
		- RESTORE new process's register state
	So what are the transitions?  The transitions out (where processor state must be saved) are the opposites of tryLockVMOwnerTo:. Hence
	- ioWaitOnOSSemaphore:
	- disownVM:
	- ioTransferTimeslice

A better approach is likely this view:

An alternative is to observe that we only enter processor code through a leaf call or an enilopmart.  cogit could have a processor owner tag, the index of the thread that currently owns the processor, and whenever we enter machine code we save the processor state if the tag doesn't match.

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

Item was changed:
  CoInterpreterPrimitives subclass: #CoInterpreterMT
  	instanceVariableNames: 'cogThreadManager checkThreadActivation maxWaitingPriority foreignCallbackPriority deferThreadSwitch disowningVMThread disownCount foreignCallbackProcessSlot activeProcessAffined relinquishing processHasThreadId reenterThreadSchedulingLoop willNotThreadWarnCount'
+ 	classVariableNames: 'DisownFlagsShift DisownVMForProcessorRelinquish OwnVMForeignThreadFlag PerThreadRumpCStackSize PrimNumberRelinquishProcessor ProcessUnaffinedOnDisown ReturnToThreadSchedulingLoop VMAlreadyOwnedHenceDoNotDisown'
- 	classVariableNames: 'DisownFlagsShift DisownVMForProcessorRelinquish OwnVMForeignThreadFlag PrimNumberRelinquishProcessor ProcessUnaffinedOnDisown ReturnToThreadSchedulingLoop VMAlreadyOwnedHenceDoNotDisown'
  	poolDictionaries: 'VMThreadingConstants'
  	category: 'VMMaker-Multithreading'!

Item was changed:
  ----- Method: CoInterpreterMT class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  
  	(InitializationOptions at: #COGMTVM ifAbsent: [false]) == false ifTrue:
  		[^self].
  
  	COGMTVM := true.
  
+ 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."
+ 
+ 	PerThreadRumpCStackSize := RumpCStackSize.
+ 	RumpCStackSize := CogThreadManager basicNew maxNumThreads * PerThreadRumpCStackSize!
- 	ReturnToThreadSchedulingLoop := 2 "setjmp/longjmp code."!

Item was changed:
  ----- Method: CoInterpreterMT>>assertSaneThreadAndProcess (in category 'debug support') -----
  assertSaneThreadAndProcess
  	<inline: true>
  	self assert: cogThreadManager vmIsOwned.
  	self assert: cogThreadManager currentVMThread state = CTMAssignableOrInVM.
+ 	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
+ 	cogThreadManager assertValidProcessorStackPointersForIndex: cogThreadManager getVMOwner!
- 	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject!

Item was changed:
  ----- Method: CoInterpreterMT>>cStackRangeForThreadIndex: (in category 'simulation') -----
  cStackRangeForThreadIndex: threadIndex
+ 	"Each simulated processor thread gets 4k of the rump C stack."
- 	"Each simulated processor thread gets 4k of the rump C stack.
- 	 The top-most section is reserved for in-memory variables such as vmOwnerLock."
  	<doNotGenerate>
  	| top |
  	^(threadIndex between: 1 and: cogThreadManager maxNumThreads) ifTrue:
+ 		[top := self rumpCStackAddress - (threadIndex - 1 * PerThreadRumpCStackSize).
+ 		 top - PerThreadRumpCStackSize + 1 to: top]!
- 		[top := self rumpCStackAddress - (threadIndex - 1 * RumpCStackSize).
- 		 top - RumpCStackSize + 1 to: top]!

Item was changed:
  ----- Method: CoInterpreterMT>>disownVM: (in category 'vm scheduling') -----
  disownVM: flags
  	"Release the VM to other threads and answer the current thread's index.
  	 Currently valid flags:
  		DisownVMForFFICall			- informs the VM that it is entering an FFI call
  		DisownVMForThreading		- informs the VM that it is entering code during which threading should be permitted
  		OwnVMForeignThreadFlag	- indicates lowest-level entry from a foreign thread
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  		VMAlreadyOwnedHenceDoNotDisown
  									- indicates an ownVM from a callback was made when
  									  the vm was still owned.
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  
  	 This is the entry-point for plugins and primitives that wish to release the VM while
  	 performing some operation that may potentially block, and for callbacks returning
  	 back to some blocking operation.  If this thread does not reclaim the VM before-
  	 hand then when the next heartbeat occurs the thread manager will schedule a
  	 thread to acquire the VM which may start running the VM in place of this thread.
  
  	 N.B. Most of the state needed to resume after preemption is set in preemptDisowningThread."
  	<api>
  	<inline: false>
  	| vmThread result |
  	self assert: (flags >= 0 and: [flags < (1 bitShift: DisownFlagsShift)]).
  	self assert: self successful.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceDisownVM thing: (objectMemory integerObjectOf: flags) source: 0].
  	processHasThreadId ifFalse:
  		[willNotThreadWarnCount < 10 ifTrue:
  			[self print: 'warning: VM parameter 48 indicates Process doesn''t have threadId; VM will not thread'; cr.
  			 willNotThreadWarnCount := willNotThreadWarnCount + 1]].
  	vmThread := cogThreadManager currentVMThread.
  	(flags anyMask: VMAlreadyOwnedHenceDoNotDisown) ifTrue:
  		[disowningVMThread := vmThread.
  		 vmThread state: CTMUnavailable.
  		 ^0].
  	self assertCStackPointersBelongToCurrentThread.
  	self assertValidNewMethodPropertyFlags.
+ 	self cCode: '' inSmalltalk:
+ 		[cogThreadManager saveRegisterStateForCurrentProcess].
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[| proc |
  		 (proc := objectMemory splObj: foreignCallbackProcessSlot) ~= objectMemory nilObject ifTrue:
  			[foreignCallbackPriority := self quickFetchInteger: PriorityIndex ofObject: proc].
  		 relinquishing := true.
  		 self sqLowLevelMFence].
  	disownCount := disownCount + 1.
  	disowningVMThread := vmThread.
  	"self cr; cr; print: 'disownVM  Csp: '; printHex: vmThread cStackPointer; cr.
  	(0 to: 16 by: 4) do:
  		[:offset|
  		self print: ' *(esp+'; printNum: offset; print: ': '; printHex: (stackPages longAt: cogit processor sp + offset); cr].
  	cogit processor printIntegerRegistersOn: Transcript."
  
  	"OwnVMForeignThreadFlag indicates lowest-level of entry by a foreign
  	 thread. If that's where we are then release the vmThread.  Otherwise
  	 indicate the vmThread is off doing something outside of the VM."
  	(flags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			["I don't think this is quite right.  Josh's use case is creating some foreign thread and then registering
  			 it with the VM. That's not the same as binding a process to a foreign thread given that the foreign
  			 callback process is about to terminate anyway (it is returning from a callback here).  So do we need
  			 an additional concept, that of a vmThread being either of the set known to the VM or floating?"
  			self flag: 'issue with registering foreign threads with the VM'.
  			(self isBoundProcess: self activeProcess) ifFalse:
  				[cogThreadManager unregisterVMThread: vmThread]]
  		ifFalse: [vmThread state: CTMUnavailable].
  	result := ((vmThread index bitShift: DisownFlagsShift)
  				 bitOr: (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown]))
  				 bitOr: flags.
  	cogThreadManager releaseVM.
  	^result!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveProcessBindToThreadId (in category 'process primitives') -----
  primitiveProcessBindToThreadId
  	"Attempt to bind the receiver to the thread with the id of the argument or nil, where the receiver is a Process.
  	 If successful the VM will ensure that there are at least id many threads active."
  	| aProcess id |
  	<export: true>
  	self cCode: [] inSmalltalk: [cogThreadManager isNil ifTrue: [^self primitiveFail]].
  	processHasThreadId ifFalse:
  		[^self primitiveFailFor: PrimErrUnsupported].
  	id := self stackTop.
  	aProcess := self stackValue: 1.
  	((id = objectMemory nilObject or: [(objectMemory isIntegerObject: id)
  										and: [id ~= (objectMemory integerObjectOf: 0)]])
  	and: [(objectMemory isPointers: aProcess)
  	and: [(objectMemory slotSizeOf: aProcess) >= (ThreadIdIndex + 1)]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	id := id = objectMemory nilObject ifTrue: [0] ifFalse: [objectMemory integerValueOf: id].
  	id abs >= cogThreadManager maxNumThreads ifTrue:
  		[^self primitiveFailFor: PrimErrLimitExceeded].
  	(self bindProcess: aProcess toId: id) ifNotNil:
  		[:ec| ^self primitiveFailFor: ec].
+ 	self methodReturnReceiver.
+ 
+ 	self halt.
  	id := self ownerIndexOfProcess: aProcess.
  	(aProcess = self activeProcess
  	and: [(activeProcessAffined := id ~= 0)
  	and: [(cogThreadManager vmOwnerIsCompatibleWith: id) not]]) ifTrue:
  		[(self quickFetchInteger: PriorityIndex ofObject: aProcess) < maxWaitingPriority ifTrue:
  			[maxWaitingPriority = self quickFetchInteger: PriorityIndex ofObject: aProcess].
+ 		 self threadSwitchIfNecessary: aProcess from: CSThreadBind]!
- 		 checkThreadActivation := true.
- 		 self forceInterruptCheck].
- 	self methodReturnReceiver!

Item was changed:
  ----- Method: CoInterpreterMT>>setCFramePointer: (in category 'simulation') -----
  setCFramePointer: cfp
  	"Set the CFramePointer, either on initialization (see initializeProcessorStack:) or from
  	 machine code in ceCaptureCStackPointers.  Unlike the superclass, CFramePointer
+ 	 will be different for each thread using the VM."
- 	 will be different for each thread using teh VM."
  	<doNotGenerate>
+ 	| index range |
+ 	index := cogThreadManager currentVMThread
+ 				ifNil: [1] "initialization..."
+ 				ifNotNil: "subsequently..."
+ 					[:currentVMThread|
+ 					 self assert: cogThreadManager getVMOwner = currentVMThread index.
+ 					 cogThreadManager getVMOwner].
+ 	range := self cStackRangeForThreadIndex: index.
+ 	self assert: (range includes: cfp).
  	^CFramePointer := cfp!

Item was added:
+ ----- Method: CoInterpreterMT>>setCFramePointer:setCStackPointer: (in category 'callback support') -----
+ setCFramePointer: cFramePointer setCStackPointer: cStackPointer
+ 	self cCode: '' inSmalltalk:
+ 		[| index range |
+ 		index := CStackPointer
+ 					ifNil: [1] "first time..."
+ 					ifNotNil: "subsequently..."
+ 						[self assert: cogThreadManager getVMOwner = cogThreadManager currentVMThread index.
+ 						 cogThreadManager getVMOwner].
+ 		range := self cStackRangeForThreadIndex: index.
+ 		self assert: ((range includes: cFramePointer)
+ 				and: [range includes: cStackPointer])].
+ 	super setCFramePointer: cFramePointer setCStackPointer: cStackPointer!

Item was changed:
  ----- Method: CoInterpreterMT>>setCStackPointer: (in category 'simulation') -----
  setCStackPointer: csp
  	"Set the CStackPointer, either on initialization (see initializeProcessorStack:) or from
  	 machine code in ceCaptureCStackPointers.  Unlike the superclass, CStackPointer
  	 will be different for each thread using the VM."
  	<doNotGenerate>
+ 	| index range |
+ 	index := cogThreadManager currentVMThread
+ 				ifNil: [1] "initialization..."
+ 				ifNotNil: "subsequently..."
+ 					[:currentVMThread|
+ 					 self assert: cogThreadManager getVMOwner = currentVMThread index.
+ 					 cogThreadManager getVMOwner].
+ 	range := self cStackRangeForThreadIndex: index.
  	^CStackPointer := csp!

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 threadSchedulingLoopImplementation: vmThread]
  		on: ReenterThreadSchedulingLoop
  		do: [:ex|
  			self assert: ex returnValue = 1.
  			reenterThreadSchedulingLoop reset.
  			ex return: true]] whileTrue!

Item was changed:
  ----- Method: CoInterpreterMT>>threadSwitchIfNecessary:from: (in category 'process primitive support') -----
  threadSwitchIfNecessary: newProc from: sourceCode
+ 	"Invoked from transferTo:from: or primitiveProcessBindToThreadId to
+ 	 switch threads if the new process is bound or affined to some other thread."
- 	"Invoked from transferTo:from: to switch threads if the new process is bound or affined to some other thread."
  	| newProcOwnerIndex vmThread activeContext |
  	self assert: (cogThreadManager vmOwnerIs: cogThreadManager ioGetThreadLocalThreadIndex).
  	deferThreadSwitch ifTrue: [^self].
  
+ 	cogThreadManager assertValidProcessorStackPointersForIndex: cogThreadManager getVMOwner.
+ 
  	"If the current process is unaffined or it is affined to the current thread we're
+ 	 ok to run, but we should yield asap if a higher-priority thread wants the VM."
- 	 ok to run, but we should yield asap if a higher-priority t6hread wants the VM."
  	newProcOwnerIndex := self ownerIndexOfProcess: newProc.
  	((activeProcessAffined := newProcOwnerIndex ~= 0)
  	 and: [(cogThreadManager vmOwnerIsCompatibleWith: newProcOwnerIndex) not]) ifFalse:
  		[(self quickFetchInteger: PriorityIndex ofObject: newProc) < maxWaitingPriority ifTrue:
  			[checkThreadActivation := true.
  			 self forceInterruptCheck].
  		^self].
  
  	"The current process is affined to a thread, but not to the current owner.  So switch to that owner."
  	self cCode: '' inSmalltalk:
  		[transcript
  			ensureCr;
+ 			f: 'threadSwitchIfNecessary: %08x from: %s(%d) owner %d -> %d\n'
+ 			printf: { newProc. TraceSources at: sourceCode. sourceCode. cogThreadManager getVMOwner. newProcOwnerIndex }].
- 			f: 'threadSwitchIfNecessary: %08x from: %d owner %d -> %d\n'
- 			printf: { newProc. sourceCode. cogThreadManager getVMOwner. newProcOwnerIndex }].
  
+ 	"We at least need to externalize the stack pointers to enable a thread switch..."
+ 	(objectMemory fetchPointer: SuspendedContextIndex ofObject: newProc) = objectMemory nilObject ifTrue:
- 	 "If the activeProcess doesn't have a context yet, it needs one from which the new thread can resume execution."
- 	 (objectMemory fetchPointer: SuspendedContextIndex ofObject: newProc) = objectMemory nilObject ifTrue:
  		[self assert: newProc = self activeProcess.
  		 self push: instructionPointer.
  		 self externalWriteBackHeadFramePointers.
+ 		 false ifTrue:
+ 			"If the activeProcess doesn't have a context yet, it needs one from which the new thread can resume execution."
+ 			[activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
+ 			 objectMemory storePointer: SuspendedContextIndex ofObject: newProc withValue: activeContext]].
- 		 activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
- 		 objectMemory storePointer: SuspendedContextIndex ofObject: newProc withValue: activeContext].
  
  	newProcOwnerIndex < 0
  		ifTrue:
  			[self assert: newProcOwnerIndex negated = cogThreadManager getVMOwner.
  			 vmThread := cogThreadManager ensureWillingThread.
  			 self deny: vmThread index = cogThreadManager getVMOwner.
  			 self assert: (cogThreadManager threadIndex: vmThread index isCompatibleWith: newProcOwnerIndex)]
  		ifFalse:
  			[vmThread := cogThreadManager vmThreadAt: newProcOwnerIndex.
  			 vmThread priority: (self quickFetchInteger: PriorityIndex ofObject: newProc).
  			 vmThread state = CTMUnavailable ifTrue:
  				[vmThread state: CTMWantingOwnership]].
  	 self returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: CSSwitchIfNeccessary!

Item was changed:
  ----- Method: CogThreadManager>>assertValidStackPointersInState:forIndex: (in category 'simulation') -----
  assertValidStackPointersInState: registerState forIndex: threadIndex
  	| time range |
  	time := Time utcMicrosecondClock.
  	range := coInterpreter cStackRangeForThreadIndex: threadIndex.
  	self assert: ((range includes: (registerState at: cogit processor registerStateFPIndex))
  				and: [range includes: (registerState at: cogit processor registerStateSPIndex)])
  
+ 	"(1 to: self maxNumThreads) collect:
+ 		[:i| | range |
+ 		range := coInterpreter cStackRangeForThreadIndex: i.
+ 		range storeStringBase: 16]"
+ 
+ 	"(1 to: self maxNumThreads)
- 	"(0 to: numThreads + numThreadsIncrement)
  		detect:
  			[:i| | range |
+ 			range := coInterpreter cStackRangeForThreadIndex: i.
- 			range := coInterpreter cStackRangeForThreadIndex: threadIndex.
  			((range includes: (registerState at: cogit processor registerStateFPIndex))
  			and: [range includes: (registerState at: cogit processor registerStateSPIndex)])]
  		ifNone: []"
  
+ 	"{ (registerState at: cogit processor registerStateFPIndex) hex.
+ 		coInterpreter whereIs: (registerState at: cogit processor registerStateFPIndex).
+ 		(registerState at: cogit processor registerStateSPIndex) hex.
+ 		coInterpreter whereIs: (registerState at: cogit processor registerStateSPIndex) }"
+ 
+ 	"(1 to: self maxNumThreads)
+ 		detect:
+ 			[:i| | range |
+ 			range := coInterpreter cStackRangeForThreadIndex: i.
+ 			((range includes: cogit processor fp)
+ 			and: [range includes: cogit processor sp])]
+ 		ifNone: []"
+ 
+ 	"{ cogit processor fp hex.
+ 		coInterpreter whereIs: cogit processor fp.
+ 		cogit processor sp hex.
+ 		coInterpreter whereIs: cogit processor sp }"!
- 	"{ coInterpreter whereIs: (registerState at: cogit processor registerStateFPIndex).
- 		coInterpreter whereIs: (registerState at: cogit processor registerStateSPIndex) }"!

Item was added:
+ ----- Method: CogThreadManager>>initializeProcessor:forThreadIndex: (in category 'simulation') -----
+ initializeProcessor: aProcessor forThreadIndex: threadIndex
+ 	"Initialize aProcessor with stack pointers within its defined range."
+ 	<doNotGenerate>
+ 	| range |
+ 	range := coInterpreter cStackRangeForThreadIndex: threadIndex.
+ 	aProcessor smashCallerSavedRegistersWithValuesFrom: 16r90000000 by: coInterpreter objectMemory wordSize / 2.
+ 	 cogit initializeProcessorStack: range last.
+ 	 self assertValidProcessorStackPointersForIndex: threadIndex!

Item was changed:
  ----- Method: CogThreadManager>>ioTransferTimeslice (in category 'simulation') -----
  ioTransferTimeslice
  	<doNotGenerate>
  	"See platforms/Cross/vm/sq.h for the real definition."
+ 	self saveRegisterStateForCurrentProcess.
  	Processor yield!

Item was changed:
  ----- Method: CogThreadManager>>ioWaitOnOSSemaphore: (in category 'simulation') -----
  ioWaitOnOSSemaphore: aSemaphorePtr
  	<var: #anOSSemaphore type: #'sqOSSemaphore *'>
  	<returnTypeC: #void>
  	<doNotGenerate>
  	"See platforms/Cross/vm/sq.h for the real definition."
  	"Simulate the VM's heartbeat by calling checkVMOwnershipFromHeartbeat
  	 if the wait times-out."
+ 	self saveRegisterStateForCurrentProcess.
+ 
- 	| thisThread |
  	[aSemaphorePtr value waitTimeoutMSecs: 1000] whileTrue:
+ 		[coInterpreter checkVMOwnershipFromHeartbeat]!
- 		[coInterpreter checkVMOwnershipFromHeartbeat].
- 	self deny: vmOwner = 0.
- 	thisThread := self vmThreadForCurrentProcess.
- 	cogit withProcessorHaltedDo:
- 		[| processor |
- 		processor := cogit processor.
- 		registerStates
- 			at: thisThread index
- 			ifPresent:
- 				[:registerState|
- 				self assertValidStackPointersInState: registerState forIndex: thisThread index].
- 		processor setRegisterState: (registerStates
- 										at: thisThread index
- 										ifAbsentPut:
- 											[self ensureInitializedProcessor: processor forThreadIndex: thisThread index.
- 											 processor registerState])]!

Item was added:
+ ----- Method: CogThreadManager>>saveRegisterStateForCurrentProcess (in category 'simulation') -----
+ saveRegisterStateForCurrentProcess
+ 	"On switching osProcess we have to both
+ 	- SAVE old process's register state
+ 	- RESTORE new process's register state
+ 		So what are the transitions?  The transitions out (where processor state must be saved) are the opposites of tryLockVMOwnerTo:.
+ 		Hence
+ 		- waitOnOSSemaphore:
+ 		- disownVM:
+ 		- ioTransferTimeslice
+ 	 i.e. the continuations from here, disownVM:, and ioTransferTimeslice, will use tryLockVMOwnerTo:
+ 	 to regain control of the VM. So the register state to be restored at that point (if tryLockVMOwnerTo:
+ 	 succeeds) is the register state saved in one of the three places.
+ 	 But the processor is initialized in tryLockVMOwnerTo:, so only save the state if state is already present."
+ 	<doNotGenerate>
+ 	cogit withProcessorHaltedDo:
+ 		[| currentVMThread state |
+ 		currentVMThread := self vmThreadForCurrentProcess.
+ 		(registerStates includesKey: currentVMThread index) ifTrue:
+ 			[state := cogit processor registerState.
+ 			self assertValidStackPointersInState: state forIndex: currentVMThread index.
+ 			registerStates at: currentVMThread index put: state]]!

Item was changed:
  ----- Method: CogThreadManager>>setVMOwner: (in category 'public api') -----
  setVMOwner: indexOrZero
  	"An ugly accessor used in only three cases:
  	 1.	by ownVMFromUnidentifiedThread when the VM is first locked to the thread id
  		of the unidentified thread, and then, once identified, to the thread's index.
  	 2.	by wakeVMThreadFor: used by the two-level scheduler to switch threads when
  		a Smalltalk process switch occurs to a process affined to another thread.
  	 3. to release the VM (set the owner to zero)"
  	<inline: #always>
  	self cCode: '' inSmalltalk:
  		[coInterpreter transcript
  			ensureCr;
  			f: 'setVMOwner: %d -> %d (%s)\n'
+ 			printf: { vmOwner. indexOrZero. thisContext home sender selector }].
- 			printf: { vmOwner. indexOrZero. thisContext home sender selector }.
- 		"In the simulation this is where register state is saved; it is switched here and in tryLockVMOwnerTo:."
- 		(vmOwner ~= 0 and: [vmOwner ~= indexOrZero]) ifTrue:
- 			[self assertValidProcessorStackPointersForIndex: vmOwner.
- 			 registerStates at: vmOwner put: cogit processor registerState].
- 		(registerStates at: indexOrZero ifPresent: [:registerState| cogit processor setRegisterState: registerState])].
  	vmOwner := indexOrZero.
  	self sqLowLevelMFence!

Item was changed:
  ----- Method: CogThreadManager>>tryLockVMOwnerTo: (in category 'simulation') -----
  tryLockVMOwnerTo: threadIndex
  	"In the real VM this is a direct call of Cogit>>#tryLockVMOwnerTo:/ceTryLockVMOwner.
+ 	 In the simulation this is where register state is restored, simulating a thread switch.
+ 	 State is stored in saveRegisterStateForCurrentProcess (sent by disownVM:, ioWaitOnOSSemaphore:
+ 	 and ioTransferTimeslice).  The code here and in saveRegisterStateForCurrentProcess allow us to
+ 	 avoid the expensive and complex MultiProcessor hack.
+ 
+ 	 The idea here is to save the register state around the invocation of tryLockVMOwnerTo:, and set
+ 	 the register state to that for the owner, changing the state if ownership has changed, restoring
+ 	 it if ownership has not changed."
- 	 In the simulation this is where register state is saved and switched, simulating a thread
- 	 switch. setVMOwner: also saves register state.  The code here and in setVMOwner: allow
- 	 us to avoid the expensive and complex MultiProcessor hack."
  	<doNotGenerate>
- 	| result |
  	self deny: threadIndex = 0.
+ 	^cogit withProcessorHaltedDo:
+ 		[| currentOwner prior processor result |
- 	cogit withProcessorHaltedDo:
- 		[| currentOwner prior processor  |
  		processor := cogit processor.
+ 		currentOwner := vmOwner.
+ 		vmOwner ~= 0 ifTrue:
+ 			[prior := processor registerState.
+ 			 self assertValidStackPointersInState: prior forIndex: vmOwner].
+ 		processor setRegisterState: (registerStates
+ 										at: threadIndex
+ 										ifAbsentPut:
+ 											[self initializeProcessor: processor forThreadIndex: threadIndex.
+ 											 processor registerState]).
- 		prior := processor registerState.
- 		"A thread switch would (have) occur(ed) if it were that the VM were owned other than by threadIndex"
- 		(currentOwner := vmOwner) ~= threadIndex ifTrue:
- 			[currentOwner ~= 0 ifTrue:
- 				[self assertValidStackPointersInState: prior forIndex: currentOwner.
- 				registerStates at: currentOwner put: prior].
- 			 processor setRegisterState: (registerStates
- 											at: threadIndex
- 											ifAbsentPut:
- 												[self ensureInitializedProcessor: processor forThreadIndex: threadIndex.
- 												 processor registerState])].
  		result := cogit tryLockVMOwnerTo: threadIndex.
  		self assert: result = (threadIndex = vmOwner).
  		result
  			ifTrue: [registerStates at: threadIndex put: processor registerState]
+ 			ifFalse: [prior ifNotNil: [processor setRegisterState: prior]].
- 			ifFalse: [processor setRegisterState: prior].
  		coInterpreter transcript
  			ensureCr;
  			f: (result ifTrue: ['tryLockVMOwner %d -> %d (%s) ok\n'] ifFalse: ['tryLockVMOwner %d -> %d (%s) FAILED\n'])
+ 			printf: { vmOwner. threadIndex. thisContext home sender selector }.
+ 		self assertValidProcessorStackPointersForIndex: vmOwner.
+ 		result]!
- 			printf: { currentOwner. threadIndex. thisContext home sender selector }.
- 		self assertValidProcessorStackPointersForIndex: vmOwner].
- 	^result!

Item was changed:
  ----- Method: CogVMSimulator>>isOnRumpCStack: (in category 'rump c stack') -----
  isOnRumpCStack: address
+ 	^address between: heapBase - RumpCStackSize and: heapBase - objectMemory wordSize!
- 	^address between: heapBase - self rumpCStackSize and: heapBase - objectMemory wordSize!

Item was changed:
  ----- Method: CogVMSimulator>>rumpCStackSize (in category 'rump c stack') -----
  rumpCStackSize
+ 	"Answer the size of the rump C stack used for simulation.  This stack is used for C calls,
+ 	 i.e. calls made into the simulated C run-time, typically of routines in CoInterpreter."
+ 	^RumpCStackSize!
- 	"Allocate a rump C stack for simulation.  This stack is used for C calls, i.e. calls
- 	 made into the simulated C run-time, typically of routines in CoInterpreter.
- 	 We also use it to hold in-memory copies of the cStackPointer and cFramePointer
- 	 variables for simulation speed.  Alas we don't use an in-memory copy of stackLimit,
- 	 because we need some activity to count in order to implement the ioMSecs
- 	 routine and the stackLimit check is the ideal one."
- 	^self threadManager
- 		ifNil: [RumpCStackSize]
- 		ifNotNil: [:threadManager| RumpCStackSize * (threadManager maxNumThreads + 1)]!

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



More information about the Vm-dev mailing list