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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 3 04:20:06 UTC 2022


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

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

Name: VMMaker.oscog-eem.3129
Author: eem
Time: 2 January 2022, 8:19:55.488175 pm
UUID: 1e88d1b1-a3cd-4dfa-a731-cfc7bb84c393
Ancestors: VMMaker.oscog-eem.3128

Fix backing up the pc on wait when the process being suspended has an interpreter frame that has a bytecode pc on top of stack rather than the ceReturnToInterpreterPC.

Fix a slip in statAverageLivePagesWhenMapping:

Fix printing the method field in printContext: (the oop was previously omitted)

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

Item was changed:
  ----- Method: CoInterpreter>>backupProcess:toBlockingSendTo: (in category 'process primitive support') -----
  backupProcess: aProcess toBlockingSendTo: conditionVariable
  	"Assume aProcess is waiting on a condition variable.
  	 Backup the PC of aProcess to the send that entered the wait state.
  	 Since the PC at a send is not a susension point in machine code, this
  	 entails converting a machine code frame into an interpreter frame.
  	 primitiveEnterCriticalSection pushes false for blocked waiters. false
  	 must be replaced by the condition variable."
  
  	| context theMethod pc sp theIP theNewIP theFP thePage |
  	context := objectMemory fetchPointer: SuspendedContextIndex ofObject: aProcess.
  	self assert: (objectMemory isContext: context).
  	theMethod := objectMemory fetchPointer: MethodIndex ofObject: context.
  	(self isSingleContext: context) ifTrue:
  		[pc := objectMemory fetchPointer: InstructionPointerIndex ofObject: context.
  		 sp := objectMemory fetchPointer: StackPointerIndex ofObject: context.
  		 self assert: ((objectMemory isIntegerObject: pc) and: [(objectMemory integerValueOf: pc) > 0]).
  		 self assert: ((objectMemory isIntegerObject: sp) and: [(objectMemory integerValueOf: sp) > 0]).
  		 theIP := theMethod + objectMemory baseHeaderSize + (objectMemory integerValueOf: pc) - 1.
  		 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  		 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  		 pc := theNewIP - theMethod - objectMemory baseHeaderSize + 1.
  		 objectMemory
  			storePointerUnchecked: InstructionPointerIndex
  			ofObject: context
  			withValue: (objectMemory integerObjectOf: pc).
  		 sp := (objectMemory integerValueOf: sp) + ReceiverIndex. "implicitly converts to 0 relative"
  		 self assert: ((objectMemory fetchPointer: sp ofObject: context) = objectMemory falseObject
  					or: [(objectMemory fetchPointer: sp ofObject: context) = conditionVariable]).
  		 objectMemory storePointer: sp ofObject: context withValue: conditionVariable.
  		 ^self].
  	self assert: (self isMarriedOrWidowedContext: context).
  	self deny: (self isWidowedContextNoConvert: context).
  	theFP := self frameOfMarriedContext: context.
  	thePage := stackPages stackPageFor: theFP.
  	self deny: thePage = stackPage.
  	self assert: theFP = thePage headFP.
  	(self isMachineCodeFrame: theFP)
  		ifTrue:
  			[| mcpc maybeClosure startBcpc cogMethodForIP |
  			 mcpc := stackPages longAt: thePage headSP. "a machine code pc... it must be converted..."
  			 maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: context.
  			 (maybeClosure ~= objectMemory nilObject
  			  and: [self isVanillaBlockClosure: maybeClosure])
  				ifTrue: [cogMethodForIP := self mframeHomeMethod: theFP.
  						startBcpc := self startPCOfClosure: maybeClosure]
  				ifFalse: [cogMethodForIP := self cCoerceSimple: (self mframeMethod: theFP) to: #'CogMethod *'.
  						startBcpc := self startPCOfMethod: theMethod].
  			 theIP := cogit bytecodePCFor: mcpc startBcpc: startBcpc in: cogMethodForIP.
  			 theIP := theIP + theMethod + objectMemory baseHeaderSize.
  			 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  			 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  			 self convertFrame: theFP toInterpreterFrame: theIP - theNewIP]
  		ifFalse:
+ 			[theIP := stackPages longAt: thePage headSP.
+ 			 theIP = cogit ceReturnToInterpreterPC
+ 				ifTrue:
+ 					[theIP := (self iframeSavedIP: theFP) + 1. "fetchByte uses pre-increment; must + 1 to point at correct bytecode..."
+ 					 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
+ 					 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
+ 					 self iframeSavedIP: theFP put: theNewIP - 1] "fetchByte uses pre-increment; must - 1 to fetch correct bytecode..."
+ 				ifFalse:
+ 					[theIP := theIP + 1. "fetchByte uses pre-increment; must + 1 to point at correct bytecode..."
+ 					 self assert: (self validInstructionPointer: theIP inMethod: theMethod framePointer: theFP).
+ 					 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
+ 					 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
+ 					 stackPages longAt: thePage headSP put: theNewIP - 1]]. "fetchByte uses pre-increment; must - 1 to fetch correct bytecode..."
- 			[self assert: (stackPages longAt: thePage headSP) = cogit ceReturnToInterpreterPC.
- 			 theIP := (self iframeSavedIP: theFP) + 1 "fetchByte uses pre-increment; must + 1 to point at correct bytecode...".
- 			 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
- 			 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
- 			 self iframeSavedIP: theFP put: theNewIP - 1]. "fetchByte uses pre-increment; must - 1 to fetch correct bytecode..."
  	self assert: ((stackPages longAt: thePage headSP + objectMemory wordSize) = objectMemory falseObject
  				or: [(stackPages longAt: thePage headSP + objectMemory wordSize) = conditionVariable]).
  	stackPages longAt: thePage headSP + objectMemory wordSize put: conditionVariable!

Item was changed:
  ----- Method: CoInterpreter>>printMethodFieldForPrintContext: (in category 'debug printing') -----
  printMethodFieldForPrintContext: aContext
  	<inline: true>
  	| meth |
  	meth := objectMemory fetchPointer: MethodIndex ofObject: aContext.
+ 	'%P: ' f: transcript printf: meth.
  	self printOopShortInner: meth.
  	(self methodHasCogMethod: meth) ifTrue:
+ 		[' (%P)' f: transcript printf:  (self cogMethodOf: meth)].
- 		[self space; print: '('; printHexnp: (self cogMethodOf: meth); print: ')'].
  	self cr!

Item was changed:
  ----- Method: CogStackPages>>statAverageLivePagesWhenMapping: (in category 'statistics') -----
  statAverageLivePagesWhenMapping: aFloat
  	<var: #aFloat type: #double>
+ 	aFloat = 0.0
- 	aFloat == 0.0
  		ifTrue: [statPageCountWhenMappingSum := statNumMaps := 0]
  		ifFalse: [coInterpreter primitiveFailFor: PrimErrBadArgument]!

Item was changed:
  ----- Method: StackInterpreter>>printMethodFieldForPrintContext: (in category 'debug printing') -----
  printMethodFieldForPrintContext: aContext
  	<inline: true>
+ 	| theMethod |
+ 	theMethod := objectMemory fetchPointer: MethodIndex ofObject: aContext.
+ 	'%P: ' f: transcript printf: theMethod.
+ 	self shortPrintOop: theMethod!
- 	self shortPrintOop: (objectMemory fetchPointer: MethodIndex ofObject: aContext)!



More information about the Vm-dev mailing list