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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 22 16:30:12 UTC 2021


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

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

Name: VMMaker.oscog-eem.3074
Author: eem
Time: 22 September 2021, 9:30:01.013156 am
UUID: fc13f6e9-1cc3-4535-a31d-5e7f5dafe75f
Ancestors: VMMaker.oscog-eem.3073

CoInterpreter:
Fix bad bug in justActivateNewMethod:.  If newMethod was cogged and the method must be activated as an interpreter method (i.e. primitiveFailForFFIException:at:) then the old code did not access the true methodHeader, causing a crash.

Eliminate unnecessary instructionPointer casts; it is unsigned.

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

Item was changed:
  ----- Method: CoInterpreter>>activateFailingPrimitiveMethod (in category 'primitive support') -----
  activateFailingPrimitiveMethod
+ 	"Assuming the primFailCode and any other relevant failure
+ 	 state has been set, switch the VM to the interpreter, and
+ 	 activate newMethod (which is expected to have a primitive)."
- 	"Assuming the primFailCode (and any other relevant failure state) has been set,
- 	 switch the VM to the interpreter if necessary (if in the CoInterpreter executing machine code),
- 	 and activate the newMethod (which is expected to have a primitive)."
  	self assert: primFailCode ~= 0.
  	self assert: (objectMemory addressCouldBeObj: newMethod).
  	self assert: (objectMemory isCompiledMethod: newMethod).
  	self assert: (self primitiveIndexOf: newMethod) ~= 0.
  	self justActivateNewMethod: true. "Frame must be interpreted"
  	cogit ceInvokeInterpret.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: CoInterpreter>>callbackEnter: (in category 'callback support') -----
  callbackEnter: callbackID
  	"Re-enter the interpreter for executing a callback"
  	| currentCStackPointer currentCFramePointer wasInMachineCode calledFromMachineCode |
  	<volatile>
  	<export: true>
  	<var: #currentCStackPointer type: #usqIntptr_t>
  	<var: #currentCFramePointer type: #usqIntptr_t>
  	<var: #callbackID type: #'sqInt *'>
  
  	"For now, do not allow a callback unless we're in a primitiveResponse"
  	(self asserta: primitiveFunctionPointer ~= 0) ifFalse:
  		[^false].
  
  	self assert: primFailCode = 0.
  
  	"Check if we've exceeded the callback depth"
  	(self asserta: jmpDepth < MaxJumpBuf) ifFalse:
  		[^false].
  	jmpDepth := jmpDepth + 1.
  
  	wasInMachineCode := self isMachineCodeFrame: framePointer.
  	calledFromMachineCode := instructionPointer <= objectMemory startOfMemory.
  
  	"Suspend the currently active process"
  	suspendedCallbacks at: jmpDepth put: self activeProcess.
  	"We need to preserve newMethod explicitly since it is not activated yet
  	and therefore no context has been created for it. If the caller primitive
  	for any reason decides to fail we need to make sure we execute the correct
  	method and not the one 'last used' in the call back"
  	suspendedMethods at: jmpDepth put: newMethod.
  	self flag: 'need to debug this properly.  Conceptually it is the right thing to do but it crashes in practice'.
  	false
  		ifTrue:
  			["Signal external semaphores since a signalSemaphoreWithIndex: request may
  			  have been issued immediately prior to this callback before the VM has any
  			  chance to do a signalExternalSemaphores in checkForEventsMayContextSwitch:"
  			 self signalExternalSemaphores.
  			 "If no process is awakened by signalExternalSemaphores then transfer
  			  to the highest priority runnable one."
  			 (suspendedCallbacks at: jmpDepth) = self activeProcess ifTrue:
  				[self transferTo: self wakeHighestPriority from: CSCallbackLeave]]
  		ifFalse:
  			[self transferTo: self wakeHighestPriority from: CSCallbackLeave].
  
  	"Typically, invoking the callback means that some semaphore has been 
  	signaled to indicate the callback. Force an interrupt check as soon as possible."
  	self forceInterruptCheck.
  
  	"Save the previous CStackPointers..."
  	currentCStackPointer := CStackPointer.
  	currentCFramePointer := CFramePointer.
  	cogit assertCStackWellAligned.
  	(self _setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
  		[callbackID at: 0 put: jmpDepth.
  		 self enterSmalltalkExecutive.
  		 self assert: false "NOTREACHED"].
  
  	"Restore the previous CStackPointers..."
  	self setCFramePointer: currentCFramePointer setCStackPointer: currentCStackPointer.
  
  	"Transfer back to the previous process so that caller can push result"
  	self putToSleep: self activeProcess yieldingIf: preemptionYields.
  	self transferTo: (suspendedCallbacks at: jmpDepth) from: CSCallbackLeave.
  	newMethod := suspendedMethods at: jmpDepth.	"see comment above"
  	argumentCount := self argumentCountOf: newMethod.
  	self assert: wasInMachineCode = (self isMachineCodeFrame: framePointer).
  	calledFromMachineCode
  		ifTrue:
+ 			[instructionPointer >= objectMemory startOfMemory ifTrue:
- 			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer.
  				 instructionPointer := cogit ceReturnToInterpreterPC]]
  		ifFalse:
  			["Even if the context was flushed to the heap and rebuilt in transferTo:from:
  			  above it will remain an interpreted frame because the context's pc would
  			  remain a bytecode pc.  So the instructionPointer must also be a bytecode pc."
  			 self assert: (self isMachineCodeFrame: framePointer) not.
  			 self assert: instructionPointer > objectMemory startOfMemory].
  	self assert: primFailCode = 0.
  	jmpDepth := jmpDepth-1.
  	^true!

Item was changed:
  ----- Method: CoInterpreter>>ensurePushedInstructionPointer (in category 'enilopmarts') -----
  ensurePushedInstructionPointer
  	"We're about to make some transition to a machine code method which
  	 requires the instructionPointer must be on the stack.  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.  Make sure the instruction pointer is pushed and/or saved."
+ 	instructionPointer >= objectMemory startOfMemory
- 	instructionPointer asUnsignedInteger >= objectMemory startOfMemory
  		ifTrue:
  			"invoked directly from the interpreter"
  			[self iframeSavedIP: framePointer put: instructionPointer.
  			 self push: cogit ceReturnToInterpreterPC]
  		ifFalse:
  			["instructionPointer == cogit ceReturnToInterpreterPC
  				ifTrue: [invoked from the interpreter via a machine code primitive]
  				ifFalse: [invoked from machine code].
  			 If in the first case the bytecode instructionPointer has already been
  			 saved in iframeSavedIP so all we need to do is push the instructionPointer."
  			 self push: instructionPointer]!

Item was changed:
  ----- Method: CoInterpreter>>executeNewMethod (in category 'message sending') -----
  executeNewMethod
  	"Execute newMethod - either primitiveFunctionPointer must be set directly
  	 (i.e. from primitiveExecuteMethod et al), or it would have been set probing
  	 the method cache (i.e. primitivePerform et al)."
  	| methodHeader inInterpreter |
  	inInterpreter := instructionPointer >= objectMemory startOfMemory.
  	primitiveFunctionPointer ~= 0 ifTrue:
  		[self isPrimitiveFunctionPointerAnIndex ifTrue:
  			[self externalQuickPrimitiveResponse.
  			 self return: self popStack toExecutive: inInterpreter.
  			 ^nil].
  		 "slowPrimitiveResponse may of course context-switch.  If so we must reenter the
  		  new process appopriately, returning only if we've reached here directly from the
  		  interpreter and have found an interpreter frame.  The instructionPointer tells us
  		  from whence we came."
  		 self slowPrimitiveResponse ifTrue:
  			[self return: self popStack toExecutive: inInterpreter.
  			 ^nil]].
  	methodHeader := self rawHeaderOf: newMethod.
  	"if not primitive, or primitive failed, activate the method"
  	(self isCogMethodReference: methodHeader)
  		ifTrue:
+ 			[instructionPointer >= objectMemory startOfMemory ifTrue:
- 			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer asInteger.
  				 instructionPointer := cogit ceReturnToInterpreterPC].
  			self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: inInterpreter]
  		ifFalse:
  			[self activateNewMethod]!

Item was changed:
  ----- Method: CoInterpreter>>executeNewMethodJitting (in category 'message sending') -----
  executeNewMethodJitting
  	"Execute newMethod - either primitiveFunctionPointer must be set directly
  	 (i.e. from primitiveExecuteMethod et al), or it would have been set probing
  	 the method cache (i.e. primitivePerform et al).
  	 Eagerly compile it if appropriate so that doits are fast."
  	| methodHeader inInterpreter |
  	inInterpreter := instructionPointer >= objectMemory startOfMemory.
  	primitiveFunctionPointer ~= 0 ifTrue:
  		[self isPrimitiveFunctionPointerAnIndex ifTrue:
  			[self externalQuickPrimitiveResponse.
  			 self return: self popStack toExecutive: inInterpreter.
  			 ^nil].
  		 "slowPrimitiveResponse may of course context-switch.  If so we must reenter the
  		  new process appopriately, returning only if we've reached here directly from the
  		  interpreter and have found an interpreter frame.  The instructionPointer tells us
  		  from whence we came."
  		 self slowPrimitiveResponse ifTrue:
  			[self return: self popStack toExecutive: inInterpreter.
  			 ^nil]].
  	"Eagerly compile it if appropriate so that doits are fast."
  	methodHeader := self rawHeaderOf: newMethod.
  	(self isCogMethodReference: methodHeader) ifFalse:
  		[(self methodWithHeaderShouldBeCogged: methodHeader)
  			ifTrue:
  				[cogit cog: newMethod selector: objectMemory nilObject.
  				 methodHeader := self rawHeaderOf: newMethod]
  			ifFalse: [self maybeFlagMethodAsInterpreted: newMethod]].
  	"if not primitive, or primitive failed, activate the method"
  	(self isCogMethodReference: methodHeader)
  		ifTrue:
+ 			[instructionPointer >= objectMemory startOfMemory ifTrue:
- 			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer asInteger.
  				 instructionPointer := cogit ceReturnToInterpreterPC].
  			self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: inInterpreter]
  		ifFalse:
  			[self activateNewMethod]!

Item was changed:
  ----- Method: CoInterpreter>>justActivateNewMethod: (in category 'message sending') -----
  justActivateNewMethod: mustBeInterpreterFrame
  	| methodHeader cogMethod numArgs numTemps rcvr initialIP |
- 	<var: #cogMethod type: #'CogMethod *'>
  	<var: #initialIP type: #usqInt>
  	<inline: true>
  	methodHeader := self rawHeaderOf: newMethod.
+ 	cogMethod := nil.
+ 	(self isCogMethodReference: methodHeader) ifTrue:
- 	(mustBeInterpreterFrame not
- 	 and: [self isCogMethodReference: methodHeader]) ifTrue:
  		[cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
+ 		 methodHeader := cogMethod methodHeader.
+ 		 mustBeInterpreterFrame ifTrue:
+ 			[cogMethod := nil]].
- 		 methodHeader := cogMethod methodHeader].
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	(cogMethod notNil
+ 	 and: [(self isMachineCodeFrame: framePointer) not]) ifTrue:
+ 		[instructionPointer >= objectMemory startOfMemory ifTrue:
+ 			[self iframeSavedIP: framePointer put: instructionPointer].
- 	and: [instructionPointer asUnsignedInteger >= objectMemory startOfMemory]) ifTrue:
- 		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	initialIP := self initialIPForHeader: methodHeader method: newMethod.
  	cogMethod
  		ifNotNil:
  			[self push: cogMethod asUnsignedInteger.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
  		ifNil:
  			[self push: newMethod.
  			 self setMethod: newMethod methodHeader: methodHeader.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  			 self push: 0. "FoxIFSavedIP"
  			 instructionPointer := initialIP - 1].
  	self push: rcvr.
  
  	"clear remaining temps to nil"
+ 	numArgs + 1 to: numTemps do:
- 	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 cogMethod ifNil:
  			[instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)].
  		 primFailCode ~= 0 ifTrue:
  			[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
  
  	^methodHeader!

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.
  	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).
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  	"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.
  	"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 <= objectMemory startOfMemory!
- 		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory!

Item was changed:
  ----- 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 < objectMemory startOfMemory!
- 		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory!

Item was changed:
  ----- Method: CogThreadManager>>vmThreadAt: (in category 'public api') -----
  vmThreadAt: index
+ 	<returnTypeC: #'CogVMThread *'>
  	self assert: (index between: 0 and: numThreads).
  	^index > 0 ifTrue: [threads at: index]!



More information about the Vm-dev mailing list