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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 10 00:38:20 UTC 2020


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

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

Name: VMMaker.oscog-eem.2872
Author: eem
Time: 9 November 2020, 4:38:11.22011 pm
UUID: 5d072666-2fed-4361-871b-354b8e6f93e2
Ancestors: VMMaker.oscog-eem.2871

COGMTVM:
Change the lock to Cogit>>tryLockVMOwnerTo: from tryLockVMOwner: & tryLockVMToIndex:.
Clean up various asserts; in partcular match simulator stack depth checks in disownVM: and ownVM:.

Have print[Stack]CallStackOf: handle the active process (suspendedContext isNil).

Slang: give flexibility to the simulator by only performing a translation-time super expension if the super selector is the same as the current method's.

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

Item was added:
+ ----- Method: CoInterpreterMT>>assertCStackAssignedToCurrentThread (in category 'debug support') -----
+ assertCStackAssignedToCurrentThread
+ 	"void in production; see the simulator subclass..."
+ 	<inline: #always>!

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:
  		DisownVMLockOutFullGC	- prevent fullGCs while this thread disowns the VM
  		DisownVMForFFICall			- informs the VM that it is entering an FFI call
  		DisownVMForThreading		- informs the VM that it is entering an FFI call etc 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 |
  	<var: #vmThread type: #'CogVMThread *'>
  	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 cCode: ''
- 		inSmalltalk:
- 			[| range |
- 			 range := self cStackRangeForThreadIndex: vmThread index.
- 			 self assert: (range includes: CStackPointer).
- 			 self assert: (range includes: CFramePointer)].
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[| proc |
  		 (proc := objectMemory splObj: foreignCallbackProcessSlot) ~= objectMemory nilObject ifTrue:
  			[foreignCallbackPriority := self quickFetchInteger: PriorityIndex ofObject: proc].
  		 relinquishing := true.
  		 self sqLowLevelMFence].
  	(flags anyMask: DisownVMLockOutFullGC) ifTrue:
  		[objectMemory incrementFullGCLock].
  	(noThreadingOfGUIThread and: [self inGUIThread]) ifTrue:
  		[^vmThread index
  		 + LockGUIThreadFlag
  		 + (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
  		 + (flags << DisownFlagsShift)].
  	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
  				+ (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
  				+ (flags << DisownFlagsShift).
  	cogThreadManager releaseVM.
  	^result!

Item was removed:
- ----- Method: CoInterpreterMT>>initializeProcessorStackForSimulation: (in category 'initialization') -----
- initializeProcessorStackForSimulation: vmThread
- 	<inline: #always>
- 	self cCode: [] inSmalltalk:
- 		[| range |
- 		 range := self cStackRangeForThreadIndex: vmThread index.
- 		 cogit processor
- 			setFramePointer: range last
- 			stackPointer: range last - 32.
- 		 self setCFramePointer: cogit processor fp setCStackPointer: cogit processor sp]!

Item was changed:
  ----- Method: CoInterpreterMT>>ownVMFromUnidentifiedThread (in category 'vm scheduling') -----
  ownVMFromUnidentifiedThread
  	"Attempt to take ownership from a thread that as yet doesn't know its index.
  	 This supports callbacks where the callback could originate from any thread.
  	
  	 Answer 0 if the owning thread is known to the VM.
  	 Answer 1 if the owning thread is unknown to the VM and now owns the VM.
  	 Answer -1 if the owning thread is unknown to the VM and fails to own the VM.
  	 Answer -2 if the owning thread is unknown to the VM and there is no foreign callback process installed."
  	| count threadIndex vmThread |
  	<var: #vmThread type: #'CogVMThread *'>
  	<inline: false>
  	(threadIndex := cogThreadManager ioGetThreadLocalThreadIndex) ~= 0 ifTrue:
  		[ "this is a callback from a known thread"
  		 (cogThreadManager vmOwnerIs: threadIndex) ifTrue: "the VM has not been disowned"
  			[self assert: (disowningVMThread isNil or: [disowningVMThread = self currentVMThread]).
  			 disowningVMThread := nil.
  			 self currentVMThread state: CTMAssignableOrInVM.
  			 ^VMAlreadyOwnedHenceDoNotDisown].
  		 ^self ownVM: threadIndex].
  	foreignCallbackPriority = 0 ifTrue:
  		[^-2].
  	count := 0.
  	"If the current thread doesn't have an index it's new to the vm
  	 and we need to allocate a new threadInfo, failing if we can't.
  	 We also need a process in the foreignCallbackProcessSlot upon
  	 which to run the thread's eventual callback."
+ 	[[cogit tryLockVMOwnerTo: cogThreadManager ioCurrentOSThread] whileFalse:
- 	[[cogit tryLockVMToIndex: cogThreadManager ioCurrentOSThread] whileFalse:
  		[self waitingPriorityIsAtLeast: foreignCallbackPriority. 
  		cogThreadManager ioTransferTimeslice].
  	 (objectMemory splObj: foreignCallbackProcessSlot) ~= objectMemory nilObject] whileFalse:
  		[cogThreadManager releaseVM.
  		 (count := count + 1) > 1000 ifTrue:
  			[^-2].
  		 cogThreadManager ioMilliSleep: 1].
  
  	vmThread := cogThreadManager unusedThreadInfo.
  	"N.B.  Keep the VM locked anonymously so that we reserve the non-nil ForeignCallbackProcess
  	 for this thread, avoiding the race between competing foreign callbacks.  The acquireVMFor: in
  	 ownVM: will set the vmOwner to the actual index.  So only unlock on failure."
  	vmThread ifNil:
  		[cogThreadManager releaseVM.
  		^-1].
  	cogThreadManager setVMOwner: vmThread index.
  	vmThread
  		state: CTMWantingOwnership;
  		priority: foreignCallbackPriority.
  	cogThreadManager registerVMThread: vmThread.
  	^self ownVM: vmThread index + OwnVMForeignThreadFlag!

Item was changed:
  ----- Method: CoInterpreterMT>>preemptDisowningThread (in category 'vm scheduling') -----
  preemptDisowningThread
  	"Set the relevant state for disowningVMThread so that it can resume after
  	 being preempted and set disowningVMThread to nil to indicate preemption.
  
  	 N.B.  This should only be sent from checkPreemptionOfDisowningThread.
  
  	 There are essentially four things to do.
  	 a)	save the VM's notion of the current C stack pointers; these are pointers
  		into a thread's stack and must be saved and restored in thread switch.
  	 b)	save the VM's notion of the current Smalltalk execution point.  This is
  		simply the suspend half of a process switch that saves the current context
  		in the current process.
  	 c)	add the process to the thread's set of AWOL processes so that the scheduler
  		won't try to run the process while the thread has disowned the VM.
  	 d)	save the in-primitive VM state, newMethod and argumentCount
  
  	 ownVM: will restore the VM context as of disownVM: from the above when it
  	 finds it has been preempted."
  
  	| activeProc activeContext preemptedThread |
  	<var: #preemptedThread type: #'CogVMThread *'>
  	<inline: false>
  	self assert: disowningVMThread notNil.
  	self assert: (disowningVMThread state = CTMUnavailable
  				or: [disowningVMThread state = CTMWantingOwnership]).
+ 	self assertCStackPointersBelongToDisowningThread.
- 	self cCode: ''
- 		inSmalltalk:
- 			[| range |
- 			 range := self cStackRangeForThreadIndex: disowningVMThread index.
- 			 disowningVMThread index = cogThreadManager getVMOwner
- 				ifTrue: [self assert: ((range includes: CStackPointer) and: [range includes: CFramePointer])]
- 				ifFalse: [self deny: ((range includes: CStackPointer) or: [range includes: CFramePointer])]].
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TracePreemptDisowningThread
  			thing: (objectMemory integerObjectOf: disowningVMThread index)
  			source: 0].
  	disowningVMThread cStackPointer: CStackPointer.
  	disowningVMThread cFramePointer: CFramePointer.
  	activeProc := self activeProcess.
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject.
  	objectMemory
  		storePointer: MyListIndex
  		ofObject: activeProc
  		withValue: (objectMemory splObj: ProcessInExternalCodeTag).
  	"The instructionPointer must be pushed because the convention for inactive stack pages is that the
  	 instructionPointer is top of stack.  We need to know if this primitive is called from machine code
  	 because the invariant that the return pc of an interpreter callee calling a machine code caller is
  	 ceReturnToInterpreterPC must be maintained."
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  	"Since pushing the awol process may realloc disowningVMThread we need to reassign.
  	 But since we're going to nil disowningVMThread anyway we can assign to a local."
  	preemptedThread := cogThreadManager pushAWOLProcess: activeProc on: disowningVMThread.
  	disowningVMThread := nil.
  	preemptedThread priority: (self quickFetchInteger: PriorityIndex ofObject: activeProc).
  	(self ownerIndexOfProcess: activeProc) = 0
  		ifTrue: [self setOwnerIndexOfProcess: activeProc to: preemptedThread index bind: false]
  		ifFalse: [self assert: (self ownerIndexOfProcess: activeProc) = preemptedThread index].
  	preemptedThread
  		newMethodOrNull: newMethod;
  		argumentCount: argumentCount;
  		primitiveFunctionPointer: primitiveFunctionPointer;
  		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory!

Item was changed:
  ----- Method: CoInterpreterMT>>restoreVMStateFor:threadIndexAndFlags: (in category 'vm scheduling') -----
  restoreVMStateFor: vmThread threadIndexAndFlags: threadIndexAndFlags
  	"We've been preempted; we must restore state and update the threadId
  	 in our process, and may have to put the active process to sleep."
  	| sched activeProc myProc |
  	sched := self schedulerPointer.
  	activeProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	(threadIndexAndFlags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			[self assert: foreignCallbackProcessSlot == ForeignCallbackProcess.
  			 myProc := objectMemory splObj: foreignCallbackProcessSlot.
  			self assert: myProc ~= objectMemory nilObject.
  			objectMemory splObj: foreignCallbackProcessSlot put: objectMemory nilObject]
  		ifFalse: [myProc := cogThreadManager popAWOLProcess: vmThread].
  	self assert: activeProc ~= myProc.
  	(activeProc ~= objectMemory nilObject
  	 and: [(objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject]) ifTrue:
  		[self putToSleep: activeProc yieldingIf: preemptionYields].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: myProc) = (objectMemory splObj: ProcessInExternalCodeTag).
  	objectMemory
  		storePointer: ActiveProcessIndex ofObject: sched withValue: myProc;
  		storePointerUnchecked: MyListIndex ofObject: myProc withValue: objectMemory nilObject.
  	"Only unaffine if the process was affined at this level and did not become bound in the interim."
  	((threadIndexAndFlags anyMask: ProcessUnaffinedOnDisown)
  	 and: [(self isBoundProcess: myProc) not]) ifTrue:
  		[self setOwnerIndexOfProcess: myProc to: 0 bind: false].
  	self initPrimCall.
+ 	"Bypass the no-offset stack depth check in the simulator's externalSetStackPageAndPointersForSuspendedContextOfProcess:"
+ 	super externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
+ 	"We're in ownVM:, hence in a primitive, hence need to include the argument count"
+ 	(self isMachineCodeFrame: framePointer) ifTrue:
+ 		[self maybeCheckStackDepth: vmThread argumentCount
+ 			sp: stackPointer
+ 			pc: instructionPointer].
- 	self externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
  	"If this primitive is called from machine code maintain the invariant that the return pc
  	 of an interpreter callee calling a machine code caller is ceReturnToInterpreterPC."
  	(vmThread inMachineCode
  	 and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	newMethod := vmThread newMethodOrNull.
  	argumentCount := vmThread argumentCount.
  	primitiveFunctionPointer := vmThread primitiveFunctionPointer.
  	vmThread newMethodOrNull: nil.
  	self cCode: '' inSmalltalk:
  		[| range |
  		 range := self cStackRangeForThreadIndex: vmThread index.
  		 self assert: ((range includes: vmThread cStackPointer) and: [range includes: vmThread cFramePointer])].
  	self setCFramePointer: vmThread cFramePointer setCStackPointer: vmThread cStackPointer.
  	self assert: newMethod notNil
  !

Item was added:
+ ----- Method: CoInterpreterMT>>saveVMStateFor:threadIndexAndFlags: (in category 'vm scheduling') -----
+ saveVMStateFor: vmThread threadIndexAndFlags: threadIndexAndFlags
+ 	"Save the VM state for the disowning thread."
+ 
+ 	vmThread
+ 		newMethodOrNull: newMethod;
+ 		argumentCount: argumentCount;
+ 		primitiveFunctionPointer: primitiveFunctionPointer;
+ 		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory!

Item was added:
+ ----- 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 teh VM."
+ 	<doNotGenerate>
+ 	^CFramePointer := cfp!

Item was added:
+ ----- 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>
+ 	^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)'>
+ 	self initializeProcessorForThreadIndex: vmThread index.
- 	self initializeProcessorStackForSimulation: vmThread.
  	[([self threadSchedulingLoopImplementation: vmThread]
  		on: ReenterThreadSchedulingLoop
  		do: [:ex| ex return: ex returnValue]) = ReenterThreadSchedulingLoop] whileTrue!

Item was changed:
  ----- Method: CoInterpreterMT>>threadSchedulingLoopImplementation: (in category 'vm scheduling') -----
  threadSchedulingLoopImplementation: 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.
  	 We will return to this via threadSwitchIfNecessary:from: which is called in the
  	 middle of transferTo:from: once the active process has been stored in the scheduler."
  	<var: #vmThread type: #'CogVMThread *'>
  	| attemptToRun |
  	<inline: false>
  	self _setjmp: reenterThreadSchedulingLoop.
  	[self assert: vmThread state = CTMAssignableOrInVM.
  	 attemptToRun := false.
  	 (cogThreadManager vmOwnerIs: vmThread index)
  		ifTrue: [attemptToRun := true]
  		ifFalse:
+ 			[(cogit tryLockVMOwnerTo: vmThread index) ifTrue:
- 			[(cogit tryLockVMToIndex: vmThread index) ifTrue:
  				["If relinquishing is true, then primitiveRelinquishProcessor has disowned the
  				  VM and only a returning call or callback should take ownership in that case."
  				 relinquishing
  					ifTrue: [cogThreadManager releaseVM]
  					ifFalse: [attemptToRun := true]]].
  	 attemptToRun ifTrue:
  		[self tryToExecuteSmalltalk: vmThread].
  	 (cogThreadManager vmOwnerIs: vmThread index) ifFalse:
  		[cogThreadManager waitForWork: vmThread].
  	 true] whileTrue!

Item was changed:
  ----- Method: CogThreadManager>>acquireVMFor: (in category 'public api') -----
  acquireVMFor: threadIndex
  	"Attempt to acquire the VM, eventually blocking until it becomes available.
  	 Spin until the maxWaitingPriority has been updated if it is lower than this thread's priority."
  	<returnTypeC: #'CogVMThread *'>
  	| vmThread |
  	<var: #vmThread type: #'CogVMThread *'>
  	self assert: threadIndex = self ioGetThreadLocalThreadIndex.
  	vmThread := self vmThreadAt: threadIndex.
  	self assert: (vmThread state = CTMUnavailable
  				or: [vmThread state = CTMWantingOwnership]).
+ 	(cogit tryLockVMOwnerTo: threadIndex) ifFalse:
- 	(cogit tryLockVMOwner: threadIndex) ifFalse:
  		[vmThread state: CTMWantingOwnership.
  		 [(self vmOwnerIs: threadIndex)
+ 		  or: [cogit tryLockVMOwnerTo: threadIndex]] whileFalse:
- 		  or: [cogit tryLockVMOwner: threadIndex]] whileFalse:
  			[[coInterpreter getMaxWaitingPriority < vmThread priority] whileTrue:
  				[coInterpreter waitingPriorityIsAtLeast: vmThread priority].
  			 (self vmOwnerIs: threadIndex) ifFalse:
  				[self ioWaitOnOSSemaphore: (self addressOf: vmThread osSemaphore)]]].
  	vmOSThread := vmThread osThread.
  	vmThread state: CTMAssignableOrInVM.
  	^vmThread!

Item was changed:
  ----- Method: CogThreadManager>>ensureRunningVMThread: (in category 'public api') -----
  ensureRunningVMThread: vmIsRelinquishing
  	"Called from checkVMOwnershipFromHeartbeat if the VM is unowned.
  	 Hence we are in the heartbeat thread.  The race is against that thread
  	 owning the VM and against foreign callbacks."
  	<returnTypeC: #void>
  	<var: #vmThread type: #'CogVMThread *'>
  	self willingVMThread ifNotNil:
  		[:vmThread|
  		 "If the VM is relinquishing the processor then only schedule a thread if it has work to do."
  		 (vmIsRelinquishing
  		  and: [vmThread state ~= CTMWantingOwnership]) ifTrue:
  			[^self].
+ 		 (cogit tryLockVMOwnerTo: vmThread index) ifFalse: "someone beat us to it..."
- 		 (cogit tryLockVMToIndex: vmThread index) ifFalse: "someone beat us to it..."
  			[^self].
  		 vmOSThread := vmThread osThread.
  		 "release the thread from its blocking loop"
  		 self ioSignalOSSemaphore: (self addressOf: vmThread osSemaphore).
  		 self ioTransferTimeslice.
  		 "self cCode: [coInterpreter print: 'ERVT signalled '; printNum: vmThread index; cr]."
  		 ^self].
  
  	"If the VM is relinquishing the processor then only schedule a thread if it has work to do
  	 (willingVMThread not nil above).
  	 If we have failed to allocate thread storage before there is no point continuing to
  	 try to do so.  By this time we should have quite a few threads in the pool."
  	(vmIsRelinquishing or: [memoryIsScarce]) ifTrue:
  		[^self].
  	self unusedThreadInfo ifNotNil:
  		[:vmThread|
+ 		 (cogit tryLockVMOwnerTo: vmThread index) ifTrue:
- 		 (cogit tryLockVMOwner: vmThread index) ifTrue:
  			[(self startThreadForThreadInfo: vmThread) ifFalse:
  				[self releaseVM]]]!

Item was changed:
+ ----- Method: CogVMSimulator>>assertCStackPointersBelongToCurrentThread (in category 'debug support') -----
- ----- Method: CogVMSimulator>>assertCStackPointersBelongToCurrentThread (in category 'multi-threading simulation switch') -----
  assertCStackPointersBelongToCurrentThread
+ 	| ownerIndex range |
+ 	self assert: (ownerIndex := cogThreadManager getVMOwner) > 0.
+ 	self assert: ((range := self cStackRangeForThreadIndex: ownerIndex) includes: CFramePointer).
+ 	self assert: (range includes: CStackPointer)!
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
- 	^self perform: #assertCStackPointersBelongToCurrentThread
- 		withArguments: {}
- 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: CogVMSimulator>>assertCStackPointersBelongToDisowningThread (in category 'debug support') -----
+ assertCStackPointersBelongToDisowningThread
+ 	| range |
+ 	self assert: disowningVMThread notNil.
+ 	self assert: ((range := self cStackRangeForThreadIndex: disowningVMThread index) includes: CFramePointer).
+ 	self assert: (range includes: CStackPointer)!

Item was changed:
+ ----- Method: CogVMSimulator>>disownVM: (in category 'vm scheduling') -----
- ----- Method: CogVMSimulator>>disownVM: (in category 'multi-threading simulation switch') -----
  disownVM: flags
+ 	"Override to insert a stack depth check."
+ 	self assert: self successful.
+ 	(self isMachineCodeFrame: framePointer) ifTrue:
+ 		[self maybeCheckStackDepth: argumentCount
+ 			sp: stackPointer
+ 			pc: instructionPointer].
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
  	^self perform: #disownVM:
  		withArguments: {flags}
  		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

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

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

Item was removed:
- ----- Method: Cogit>>tryLockVMOwner: (in category 'multi-threading') -----
- tryLockVMOwner: value
- 	<api>
- 	"ceTryLockVMOwner does an atomic compare-and-swap of the vmOwner
- 	 variable with zero and the argument, setting vmOwner to value if it was
- 	 zero. It answers if the lock was zero and hence was acquired."
- 	<cmacro: '(value) ceTryLockVMOwner(value)'>
- 	processor abiMarshalArg0: value in: objectMemory memory.
- 	^[(self simulateLeafCallOf: ceTryLockVMOwner) ~= 0] ensure:
- 		[processor abiUnmarshal: 1]!

Item was added:
+ ----- Method: Cogit>>tryLockVMOwnerTo: (in category 'multi-threading') -----
+ tryLockVMOwnerTo: value
+ 	<api>
+ 	"ceTryLockVMOwner does an atomic compare-and-swap of the vmOwner
+ 	 variable with zero and the argument, setting vmOwner to value if it was
+ 	 zero. It answers if the lock was zero and hence was acquired."
+ 	<cmacro: '(value) ceTryLockVMOwner(value)'>
+ 	processor abiMarshalArg0: value in: objectMemory memory.
+ 	^[(self simulateLeafCallOf: ceTryLockVMOwner) ~= 0] ensure:
+ 		[processor abiUnmarshal: 1]!

Item was changed:
  ----- Method: MessageNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"Answer a TParseNode subclass equivalent of me"
  	"selector is sometimes a Symbol, sometimes a SelectorNode!!
  	 On top of this, numArgs is needed due to the (truly grody) use of
  	 arguments as a place to store the extra expressions needed to generate
  	 code for in-line to:by:do:, etc.  see below, where it is used.
  
  	 Expand super nodes in place. Elide sends of halt so that halts can be
  	 sprinkled through the simulator but will be eliminated from the generated C."
  	| rcvrOrNil sel args ifNotNilBlock |
  	rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod].
  	(rcvrOrNil notNil
  	and: [rcvrOrNil isVariable
+ 	and: [rcvrOrNil name = 'super'
+ 	and: [aTMethod selector == selector key]]]) ifTrue:
- 	and: [rcvrOrNil name = 'super']]) ifTrue:
  		[^aTMethod superExpansionNodeFor: selector key args: arguments].
  	sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key].
  	sel == #halt ifTrue: [^rcvrOrNil].
  	(sel == #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block."
  	  or: [sel == #cCode:]) ifTrue:
  		[arguments first isBlockNode ifTrue:
  			[| block |
  			 ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1
  				ifTrue: [block statements first]
  				ifFalse: [block]].
  		 (arguments first isLiteralNode
  		 and: [arguments first key isString
  		 and: [arguments first key isEmpty]]) ifTrue:
  			[^arguments first asTranslatorNodeIn: aTMethod]].
  	args := arguments
  				select: [:arg| arg notNil]
  				thenCollect: [:arg| arg asTranslatorNodeIn: aTMethod].
  	(sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue:
  		["Restore limit expr that got moved by transformToDo:"
  		 args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. 
  				  args second.
  				  args third. "add the limit var as a hidden extra argument; we may need it later"
  				  TVariableNode new setName: arguments first key}].
  	(sel == #ifTrue:ifFalse: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifFalse:. args := {args last}].
  	(sel == #ifTrue:ifFalse: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	(sel == #ifFalse:ifTrue: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args last}].
  	(sel == #ifFalse:ifTrue: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	((sel == #ifFalse: or: [sel == #or:])
  	 and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue:
  		["Restore argument block that got moved by transformOr: or transformIfFalse:"
  		 args := {(arguments at: 2) asTranslatorNodeIn: aTMethod}].
  	(args size > sel numArgs and: [sel ~~ #to:by:do:]) ifTrue: "to:by:do: has iLimiT hidden in last arg"
  		["prune the extra blocks left by ifTrue:, ifFalse:, and: & or:"
  		 self assert: args size - sel numArgs = 1.
  		 self assert: (args last isStmtList
  					  and: [args last statements size = 1
  					  and: [(args last statements first isVariable
  							or: [args last statements first isConstant])
  					  and: [#('nil' true false) includes: args last statements first nameOrValue]]]).
  		 args := args first: sel numArgs].
  	"For the benefit of later passes, e.g. value: inlining,
  	 transform e ifNotNil: [:v| ...] into  v := e. v ifNotNil: [...],
  	 which in fact means transforming (v := e) ifTrue: [:v|...] into v := e. v ifTrue: [...]."
  	((sel == #ifTrue: or: [sel == #ifFalse: or: [sel == #ifTrue:ifFalse: or: [sel == #ifFalse:ifTrue:]]])
  	 and: [receiver notNil
  	 and: [receiver isAssignmentEqualsEqualsNil
  	 and: [(ifNotNilBlock := args detect: [:arg| arg isStmtList and: [arg args size = 1]] ifNone: []) notNil]]]) ifTrue:
  		[ifNotNilBlock setArguments: #().
  		 ^TStmtListNode new
  			setArguments: #()
  			statements:
  				{	receiver receiver asTranslatorNodeIn: aTMethod.
  					TSendNode new
  						setSelector: sel
  						receiver: (TSendNode new
  									setSelector: #==
  									receiver: (receiver receiver variable asTranslatorNodeIn: aTMethod)
  									arguments: {receiver arguments first asTranslatorNodeIn: aTMethod})
  						arguments: args }].
  	((CCodeGenerator isVarargsSelector: sel)
  	 and: [args last isCollection
  	 and: [args last isSequenceable]]) ifTrue:
  		[args := args allButLast, args last].
  	^TSendNode new
  		setSelector: sel
  		receiver: rcvrOrNil
  		arguments: args!

Item was changed:
  ----- Method: StackInterpreter>>printCallStackOf: (in category 'debug printing') -----
  printCallStackOf: aContextOrProcessOrFrame
  	<api>
  	| context |
  	<inline: false>
  	(stackPages couldBeFramePointer: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackFP: (self cCoerceSimple: aContextOrProcessOrFrame to: #'char *')].
+ 	aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 		[^self printCallStackOf: (self cCode: [framePointer] inSmalltalk: [self headFramePointer])].
  	(self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackOf: (objectMemory
  									fetchPointer: SuspendedContextIndex
  									ofObject: aContextOrProcessOrFrame)].
  	context := aContextOrProcessOrFrame.
  	[context = objectMemory nilObject] whileFalse:
  		[(self isMarriedOrWidowedContext: context)
  			ifTrue:
  				[(self checkIsStillMarriedContext: context currentFP: framePointer) ifFalse:
  					[self shortPrintContext: context.
  					 ^nil].
  				 context := self shortReversePrintFrameAndCallers: (self frameOfMarriedContext: context)]
  			ifFalse:
  				[context := self printContextCallStackOf: context]]!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStackOf: (in category 'debug printing') -----
  printStackCallStackOf: aContextOrProcessOrFrame
  	<api>
  	| theFP context |
  	<var: #theFP type: #'char *'>
  	(self cCode: [false] "In the stack simulator, frame pointers are negative which upsets addressCouldBeObj:"
  		inSmalltalk: [stackPages couldBeFramePointer: aContextOrProcessOrFrame]) ifFalse:
  		[(objectMemory addressCouldBeObj: aContextOrProcessOrFrame) ifTrue:
  			[((objectMemory isContext: aContextOrProcessOrFrame)
  			  and: [self checkIsStillMarriedContext: aContextOrProcessOrFrame currentFP: nil]) ifTrue:
  				[^self printStackCallStackOf: (self frameOfMarriedContext: aContextOrProcessOrFrame) asInteger].
+ 			 aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 				[^self printStackCallStackOf: (self cCode: [framePointer] inSmalltalk: [self headFramePointer])].
  			 (self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  				[^self printCallStackOf: (objectMemory
  											fetchPointer: SuspendedContextIndex
  											ofObject: aContextOrProcessOrFrame)].
  			 ^nil]].
  
  	theFP := aContextOrProcessOrFrame asVoidPointer.
  	[context := self shortReversePrintFrameAndCallers: theFP.
  	 ((self isMarriedOrWidowedContext: context)
  	  and:
  		[theFP := self frameOfMarriedContext: context.
  		 self checkIsStillMarriedContext: context currentFP: theFP]) ifFalse:
  			[^nil]] repeat!



More information about the Vm-dev mailing list