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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 9 19:04:21 UTC 2022


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

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

Name: VMMaker.oscog-eem.3149
Author: eem
Time: 9 February 2022, 11:04:10.777055 am
UUID: e4e91830-a047-4c80-971d-ec6ebbfaf798
Ancestors: VMMaker.oscog-eem.3148

primitiveFunctionPointer is no longer part of primitive-invoke-time state, so expunge it from VMCallbackContext.

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

Item was changed:
  ----- Method: StackInterpreter>>returnAs:ThroughCallback:Context: (in category 'callback support') -----
  returnAs: returnTypeOop ThroughCallback: vmCallbackContext Context: callbackMethodContext
  	"callbackMethodContext is an activation of invokeCallback:[stack:registers:jmpbuf:].
  	 Its sender is the VM's state prior to the callback.  Reestablish that state (via longjmp),
  	 and mark callbackMethodContext as dead."
  	<export: true>
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	| calloutMethodContext theFP thePage |
  	<var: #theFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	self assert: primFailCode = 0.
  	self assert: (objectMemory isIntegerObject: returnTypeOop).
  	self assert: (objectMemory isImmediate: vmCallbackContext asInteger) not.
  	self assert: ((objectMemory addressCouldBeObj: callbackMethodContext)
  				and: [objectMemory isContext: callbackMethodContext]).
  	self assert: (debugCallbackPath := 0) = 0.
  	((objectMemory isIntegerObject: returnTypeOop)
  	 and: [self isLiveContext: callbackMethodContext]) ifFalse:
  		[self assert: (debugCallbackPath := 1) = 1.
  		 ^false].
  	calloutMethodContext := self externalInstVar: SenderIndex ofContext: callbackMethodContext.
  	(self isLiveContext: calloutMethodContext) ifFalse:
  		[self assert: (debugCallbackPath := 2) = 2.
  		 ^false].
  	self assert: (debugCallbackReturns := debugCallbackReturns + 1) > 0.
  	"self assert: debugCallbackReturns < 3802."
  	"We're about to leave this stack page; must save the current frame's instructionPointer."
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	"Mark callbackMethodContext as dead; the common case is that it is the current frame.
  	 We go the extra mile for the debugger."
  	(self isSingleContext: callbackMethodContext)
  		ifTrue:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 4) > 0.
  		 	 self markContextAsDead: callbackMethodContext]
  		ifFalse:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 8) > 0.
  		 	 theFP := self frameOfMarriedContext: callbackMethodContext.
  			 self assert: (self frameReceiver: theFP) = (objectMemory splObj: ClassAlien).
  			 framePointer = theFP "common case"
  				ifTrue:
  					[self assert: (debugCallbackPath := debugCallbackPath bitOr: 16) > 0.
  		 			 (self isBaseFrame: theFP) ifFalse: "calloutMethodContext is immediately below on the same page.  Make it current."
  						[self assert: (debugCallbackPath := debugCallbackPath bitOr: 32) > 0.
  		 				 instructionPointer := (self frameCallerSavedIP: theFP) asUnsignedInteger.
  						 stackPointer := theFP + (self frameStackedReceiverOffset: theFP) + objectMemory wordSize.
  						 framePointer := self frameCallerFP: theFP.
  						 self setMethod: (self frameMethodObject: framePointer).
  						 self restoreCStackStateForCallbackContext: vmCallbackContext.
  						 self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  						 "N.B. siglongjmp is defines as _longjmp on non-win32 platforms.
  						  This matches the use of _setjmp in ia32abicc.c."
  						 self _longjmp: vmCallbackContext trampoline _: (self integerValueOf: returnTypeOop).
  						 ^true].
  					 stackPages freeStackPage: stackPage]
  				ifFalse:
  					[self assert: (debugCallbackPath := debugCallbackPath bitOr: 64) > 0.
  		 			 self externalDivorceFrame: theFP andContext: callbackMethodContext.
  					 self markContextAsDead: callbackMethodContext]].
  	"Make the calloutMethodContext the active frame.  The case where calloutMethodContext
  	 is immediately below callbackMethodContext on the same page is handled above."
  	(self isStillMarriedContext: calloutMethodContext)
  		ifTrue:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 128) > 0.
  		 	 theFP := self frameOfMarriedContext: calloutMethodContext.
  			 thePage := stackPages stackPageFor: theFP.
  			 "findSPOf:on: points to the word beneath the instructionPointer, but
  			  there is no instructionPointer on the top frame of the current page."
  			 self assert: thePage ~= stackPage.
  			 stackPointer := thePage headFP = theFP
  								ifTrue: [thePage headSP]
  								ifFalse: [(self findSPOf: theFP on: thePage) - objectMemory wordSize].
  			 framePointer := theFP.
  			 self assert: stackPointer < framePointer]
  		ifFalse:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 256) > 0.
  		 	 thePage := self makeBaseFrameFor: calloutMethodContext.
  			 self setStackPointersFromPage: thePage].
  	instructionPointer := self popStack.
  	self setMethod: (objectMemory fetchPointer: MethodIndex ofObject: calloutMethodContext).
  	self setStackPageAndLimit: thePage.
  	self restoreCStackStateForCallbackContext: vmCallbackContext.
- 	primitiveFunctionPointer := vmCallbackContext savedPrimFunctionPointer.
  	"N.B. siglongjmp is defined as _longjmp on non-win32 platforms.
  	  This matches the use of _setjmp in ia32abicc.c."
  	self _longjmp: vmCallbackContext trampoline _: (self integerValueOf: returnTypeOop).
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallbackContext: (in category 'callback support') -----
  sendInvokeCallbackContext: vmCallbackContext
  	"Send the calllback message to Alien class with the supplied arg(s).  Use either the 1 arg
  	 invokeCallbackContext: or the 4 arg invokeCallback:stack:registers:jmpbuf: message,
  	 depending on what selector is installed in the specialObjectsArray. Note that if invoking the
  	 legacy invokeCallback:stack:registers:jmpbuf: we pass the vmCallbackContext as the jmpbuf
  	 argument (see reestablishContextPriorToCallback:). The arguments are raw C addresses and
  	 are converted to integer objects on the way. sendInvokeCallbackContext: &
  	 returnAs:ThroughCallback:Context: along with ownVM: and disownVM: conspire to save and
  	 restore newMethod, argumentCount and primitiveFunctionPointer around a callback.
  	 The VM depends on argumentCount being correct to cut-back the correct number of
+ 	 arguments on primitive return."
- 	 arguments on primitive return.  If a primitive that invokes a callback fails after invoking a
- 	 callback (a bad idea, but s**t happens during development) then newMethod is required to
- 	 activate the right faling method, and Spur expects primitiveFunctionPointer to be valid, so
- 	 asserts will fail misleadingly if not."
  	<export: true>
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	| classTag |
- 	vmCallbackContext savedPrimFunctionPointer: primitiveFunctionPointer.
  	classTag := self fetchClassTagOfNonImm: (objectMemory splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
  	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
- 	primitiveFunctionPointer ~= 0 ifTrue:
- 		[primitiveFunctionPointer := vmCallbackContext savedPrimFunctionPointer.
- 		 ^false].
  	self assert: (debugCallbackInvokes := debugCallbackInvokes + 1) > 0.
  	"self assert: debugCallbackInvokes < 3802."
  	self saveCStackStateForCallbackContext: vmCallbackContext.
  	self push: (objectMemory splObj: ClassAlien). "receiver"
  	(self argumentCountOf: newMethod) = 4 ifTrue:
  		[self push: (self positiveMachineIntegerFor: vmCallbackContext thunkp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext stackp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext intregargsp asUnsignedInteger)].
  	self push: (self positiveMachineIntegerFor: vmCallbackContext asUnsignedInteger).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
  	self justActivateNewMethod: false. "either interpreted or machine code"
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self checkForStackOverflow.
  	self assert: (self frameReceiver: framePointer) = (objectMemory splObj: ClassAlien).
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!

Item was changed:
  VMStructType subclass: #VMCallbackContext
+ 	instanceVariableNames: 'thunkp stackp intregargsp floatregargsp savedCStackPointer savedCFramePointer rvs savedMostRecentCallbackContext trampoline savedReenterInterpreter'
- 	instanceVariableNames: 'thunkp stackp intregargsp floatregargsp savedCStackPointer savedCFramePointer rvs savedPrimFunctionPointer savedMostRecentCallbackContext trampoline savedReenterInterpreter'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!

Item was removed:
- ----- Method: VMCallbackContext>>savedPrimFunctionPointer (in category 'accessing') -----
- savedPrimFunctionPointer
- 	
- 	^ savedPrimFunctionPointer
- !

Item was removed:
- ----- Method: VMCallbackContext>>savedPrimFunctionPointer: (in category 'accessing') -----
- savedPrimFunctionPointer: anObject
- 	
- 	^ savedPrimFunctionPointer := anObject.
- !



More information about the Vm-dev mailing list