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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 13 21:47:07 UTC 2023


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

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

Name: VMMaker.oscog-eem.3298
Author: eem
Time: 13 January 2023, 1:46:48.324039 pm
UUID: 835282e6-0e94-4101-a82d-46bd16786302
Ancestors: VMMaker.oscog-eem.3297

Add the benchmarks. Fix a slip in followForwardingPointersOfReceiverAndTemporariesInStackZone, which has no business calling markAndTrace: :-)

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

Item was added:
+ ----- Method: CoInterpreter class>>benchmarkFollowForwardersInStackZone (in category 'benchmarks') -----
+ benchmarkFollowForwardersInStackZone
+ 	"Answer the elapsed time in microseconds for followForwardingPointersInStackZone."
+ 
+ 	| ticksPerMicrosecond |
+ 	ticksPerMicrosecond := Time highResClockTicksPerMillisecond / 1000.0.
+ 	^self primitiveBenchmarkFollowForwardersInStackZone / ticksPerMicrosecond
+ 
+ 	"self benchmarkFollowForwardersInStackZone"!

Item was added:
+ ----- Method: CoInterpreter class>>benchmarkFollowForwardingPointersOfReceiverAndTemporariesInStackZone (in category 'benchmarks') -----
+ benchmarkFollowForwardingPointersOfReceiverAndTemporariesInStackZone
+ 	"Answer the elapsed time in microseconds for followForwardingPointersOfReceiverAndTemporariesInStackZone."
+ 
+ 	| ticksPerMicrosecond |
+ 	ticksPerMicrosecond := Time highResClockTicksPerMillisecond / 1000.0.
+ 	^self primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone / ticksPerMicrosecond
+ 
+ 	"self benchmarkFollowForwardingPointersOfReceiverAndTemporariesInStackZone"!

Item was added:
+ ----- Method: CoInterpreter class>>primitiveBenchmarkFollowForwardersInStackZone (in category 'benchmarks') -----
+ primitiveBenchmarkFollowForwardersInStackZone
+ 	"Answer the elapsed value of the high-performance clock for followForwardingPointersInStackZone"
+ 
+ 	<primitive: 'primitiveBenchmarkFollowForwardersInStackZone' module: '' error: ec>
+ 	^self primitiveFailed
+ 
+ 	"self primitiveBenchmarkFollowForwardersInStackZone"!

Item was added:
+ ----- Method: CoInterpreter class>>primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone (in category 'benchmarks') -----
+ primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone
+ 	"Answer the elapsed value of the high-performance clock for followForwardingPointersOfReceiverAndTemporariesInStackZone"
+ 
+ 	<primitive: 'primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone' module: '' error: ec>
+ 	^self primitiveFailed
+ 
+ 	"self primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone"!

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersOfReceiverAndTemporariesInStackZone (in category 'object memory support') -----
  followForwardingPointersOfReceiverAndTemporariesInStackZone
  	"A more thorough version of followForwardingPointersInStackZone that also follows all temporaries (but not stack contents after the temps).
  	 This would allow removal of the TempVectReadBarrier"
  	<option: #VMBenchmarks>
  	| theIPPtr |
  	<inline: false>
  
  	stackPage ifNil: "the system must be snapshotting; nothing to do..."
  		[self assert: (stackPages mostRecentlyUsedPage isNil or: [stackPages mostRecentlyUsedPage isFree]).
  		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
  		 ^self].
  
  	self externalWriteBackHeadFramePointers.
  
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset frameRcvrOffset methodHeader |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 theIPPtr := thePage = stackPage ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr isNil or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 self assert: (objectMemory isForwarded: (self mframeHomeMethod: theFP) methodObject) not.
  					 frameRcvrOffset := theFP + FoxMFReceiver.
  					 methodHeader := (self mframeHomeMethod: theFP) methodHeader]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop |
  						 newOop := objectMemory followForwarded: oop.
  						 offset := newOop - oop.
  						 (theIPPtr notNil
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + offset].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + offset.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)].
  					 frameRcvrOffset := theFP + FoxIFReceiver.
  					 methodHeader := objectMemory methodHeaderOf: oop].
  			 theSP := frameRcvrOffset - ((self temporaryCountOfMethodHeader: methodHeader) * objectMemory wordSize).
  			 [theSP <= frameRcvrOffset] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isOopForwarded: oop) ifTrue:
  					[oop := objectMemory followForwarded: oop.
  					 stackPages longAt: theSP put: oop].
- 				 (objectMemory isImmediate: oop) ifFalse:
- 					[objectMemory markAndTrace: oop].
  				 theSP := theSP + objectMemory wordSize].
  
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was added:
+ ----- Method: CompiledCode>>benchmarkJITReceiver (in category '*VMMaker-benchmarks') -----
+ benchmarkJITReceiver
+ 	"Answer the elapsed time in microseconds to jit the receiver."
+ 
+ 	| ticksPerMicrosecond |
+ 	ticksPerMicrosecond := Time highResClockTicksPerMillisecond / 1000.0.
+ 	^self primitiveBenchmarkJITReceiver / ticksPerMicrosecond
+ 
+ 	"| methods times nBytecodes nLiterals |
+ 	methods := self methodDict values.
+ 	times := methods collect: [:m| m benchmarkJITReceiver].
+ 	nLiterals := methods collect: #numLiterals.
+ 	nBytecodes := methods collect: [:m| m isQuick ifTrue: [1] ifFalse: [m endPC - m initialPC + 1]].
+ 	{times. nLiterals. nBytecodes} collect: [:stats| {stats min. stats max. stats average asFloat} collect: [:stat| stat roundTo: 0.001]]"!

Item was added:
+ ----- Method: CompiledCode>>primitiveBenchmarkJITReceiver (in category '*VMMaker-benchmarks') -----
+ primitiveBenchmarkJITReceiver
+ 	"Answer the elapsed value of the high-performance clock for jitting the receiver."
+ 
+ 	<primitive: 'primitiveBenchmarkJITReceiver' module: '' error: ec>
+ 	^self primitiveFailed
+ 
+ 	"(self methodDict values collect: [:m| m primitiveBenchmarkJITReceiver]) asSet asArray sort"!



More information about the Vm-dev mailing list