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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 13 20:17:47 UTC 2023


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

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

Name: VMMaker.oscog-eem.3296
Author: eem
Time: 13 January 2023, 12:17:25.933827 pm
UUID: 5669e2ed-ee0c-4eff-8d0c-db34220135d2
Ancestors: VMMaker.oscog-eem.3295

Include a small suite of VM benchmark primitives to measure the time taken by operations that are too short-lived to want to time them (because timing can have significant overhead).

Add an abstraction for identifying full block methods and use it in some asserts, etc.

Refactor followForwardingPointersInStackZone: to followForwardingPointersInStackZone since it makes no use of the becomeEffectFlags argument.

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

Item was added:
+ ----- Method: CoInterpreter>>followForwardingPointersInStackZone (in category 'object memory support') -----
+ followForwardingPointersInStackZone
+ 	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
+ 	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
+ 	 probe, since notionally objects' internals are accessed only via sending messages to them,
+ 	 the exception is primitives that access the internals of the non-receiver argument(s).
+ 
+ 	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
+ 	 the receivers (including the stacked receiver for non-local return) and method references
+ 	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
+ 	 scanning all of memory as in the old become.
+ 
+ 	 Override to handle machine code frames"
+ 	| 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 |
+ 		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]
+ 				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)]].
+ 			  ((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 removed:
- ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
- followForwardingPointersInStackZone: theBecomeEffectsFlags
- 	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
- 	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
- 	 probe, since notionally objects' internals are accessed only via sending messages to them,
- 	 the exception is primitives that access the internals of the non-receiver argument(s).
- 
- 	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
- 	 the receivers (including the stacked receiver for non-local return) and method references
- 	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
- 	 scanning all of memory as in the old become.
- 
- 	 Override to handle machine code frames"
- 	| 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 |
- 		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]
- 				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)]].
- 			  ((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: 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: CoInterpreter>>isFullBlockMethod: (in category 'compiled methods') -----
+ isFullBlockMethod: aMethodObj
+ 	"Answer if the argument is a full block method or not. Full block methods
+ 	 (as introduced by the SistaV1BytecodeSet) are used to implement block
+ 	 closures and have a reference to their enclosing block or method as their
+ 	 last literal. Compiled methods have a class association as their last literal."
+ 	<api>
+ 	<inline: false>
+ 	^objectMemory isOopCompiledMethod: (self ultimateLiteralOf: aMethodObj)!

Item was changed:
+ ----- Method: CoInterpreter>>markAndTraceMachineCodeMethod: (in category 'object memory support') -----
- ----- Method: CoInterpreter>>markAndTraceMachineCodeMethod: (in category 'gc -- mark and sweep') -----
  markAndTraceMachineCodeMethod: aCogMethod
  	<var: #aCogMethod type: #'CogBlockMethod *'>
  	| homeMethod |
  	<var: #homeMethod type: #'CogMethod *'>
  	homeMethod := self asCogHomeMethod: aCogMethod.
  	objectMemory markAndTrace: homeMethod methodObject!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveBenchmarkFollowForwardersInStackZone (in category 'benchmark primitives') -----
+ primitiveBenchmarkFollowForwardersInStackZone
+ 	<option: #VMBenchmarks>
+ 	<export: true>
+ 	self primitiveReturnTimeTakenFor:
+ 		[self followForwardingPointersInStackZone]!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone (in category 'benchmark primitives') -----
+ primitiveBenchmarkFollowForwardersOfReceiverAndTemporariesInStackZone
+ 	<option: #VMBenchmarks>
+ 	<export: true>
+ 	self primitiveReturnTimeTakenFor:
+ 		[self followForwardingPointersOfReceiverAndTemporariesInStackZone]!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveBenchmarkJITReceiver (in category 'benchmark primitives') -----
+ primitiveBenchmarkJITReceiver
+ 	<option: #VMBenchmarks>
+ 	<option: #SistaV1BytecodeSet>
+ 	<export: true>
+ 	| receiverMethod cloneMethod |
+ 	receiverMethod := self stackTop.
+ 	(objectMemory isOopCompiledMethod: receiverMethod) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	(self isFullBlockMethod: receiverMethod) ifTrue:
+ 		[^self primitiveFailFor: PrimErrUnsupported].
+ 	cloneMethod := objectMemory cloneObject: receiverMethod.
+ 	cloneMethod ifNil:
+ 		[^self primitiveFailFor: PrimErrNoMemory].
+ 	self primitiveReturnTimeTakenFor:
+ 		[(cogit cog: cloneMethod selector: (self maybeSelectorOfMethod: cloneMethod)) ifNil:
+ 			[^self primitiveFailFor: PrimErrOperationFailed].
+ 		 cogit freeMethod: (self cogMethodOf: cloneMethod)]!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveReturnTimeTakenFor: (in category 'benchmark primitives') -----
+ primitiveReturnTimeTakenFor: aBlock
+ 	<option: #VMBenchmarks>
+ 	<inline: #always>
+ 	| then |
+ 	<var: 'then' type: #usqLong>
+ 	then := self ioHighResClock.
+ 	aBlock value.
+ 	self methodReturnValue: (self positive64BitIntegerFor: self ioHighResClock - then)!

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| selector cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	(self exclude: aMethodObj selector: aSelectorOop) ifTrue:
  		[^nil].
  	"In Newspeak we support anonymous accessors and hence tolerate the same
  	 method being cogged multiple times.  But only if the method class association is nil."
  	NewspeakVM
  		ifTrue:
  			[(coInterpreter methodHasCogMethod: aMethodObj) ifTrue:
  				[cogMethod := coInterpreter cogMethodOf: aMethodObj.
  				 self deny: cogMethod selector = aSelectorOop.
  				 cogMethod selector = aSelectorOop ifTrue:
  					[^cogMethod].
  				 (coInterpreter methodClassAssociationOf: aMethodObj) ~= objectMemory nilObject ifTrue:
  					[self cCode: 'extern void *firstIndexableField(sqInt)'. "Slang, au natural"
  					 self warnMultiple: cogMethod selectors: aSelectorOop.
  					^nil]]]
  		ifFalse: [self deny: (coInterpreter methodHasCogMethod: aMethodObj)].
  	selector := aSelectorOop = objectMemory nilObject
  					ifTrue: [coInterpreter maybeSelectorOfMethod: aMethodObj]
  					ifFalse: [aSelectorOop].
  	"coInterpreter stringOf: selector"
  	selector ifNotNil:
  		[coInterpreter compilationBreakpoint: selector isMNUCase: false].
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	NewspeakVM ifTrue:
  		[cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  		 cogMethod ifNotNil:
  			[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  				[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  				 cogMethod methodObject: aMethodObj.
  				 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  			^cogMethod]].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
+ 	self deny: (coInterpreter isFullBlockMethod: aMethodObj).
- 	self deny: (objectMemory isOopCompiledMethod: (coInterpreter ultimateLiteralOf: aMethodObj)).
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	receiverTags := -1. "lazy initialization"
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>cogFullBlockMethod:numCopied: (in category 'jit - api') -----
  cogFullBlockMethod: aMethodObj numCopied: numCopied
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<option: #SistaV1BytecodeSet>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	(self exclude: aMethodObj) ifTrue:
  		[^nil].
  	self deny: (coInterpreter methodHasCogMethod: aMethodObj).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
+ 	self assert: (coInterpreter isFullBlockMethod: aMethodObj).
- 	self assert: (objectMemory isOopCompiledMethod: (coInterpreter ultimateLiteralOf: aMethodObj)).
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	receiverTags := -1. "lazy initialization"
  	cogMethod := self compileCogFullBlockMethod: numCopied.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was added:
+ ----- Method: StackInterpreter>>followForwardingPointersInStackZone (in category 'object memory support') -----
+ followForwardingPointersInStackZone
+ 	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
+ 	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
+ 	 probe, since notionally objects' internals are accessed only via sending messages to them,
+ 	 the exception is primitives that access the internals of the non-receiver argument(s).
+ 
+ 	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
+ 	 the receivers (including the stacked receiver for non-local return) and method references
+ 	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
+ 	 scanning all of memory as in the old become."
+ 	| 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 theFP callerFP offset oop |
+ 		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]).
+ 			  oop := stackPages longAt: theFP + FoxReceiver.
+ 			  (objectMemory isOopForwarded: oop) ifTrue:
+ 				[stackPages
+ 					longAt: theFP + FoxReceiver
+ 					put: (objectMemory followForwarded: oop)].
+ 			  ((self frameHasContext: theFP)
+ 			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
+ 				[stackPages
+ 					longAt: theFP + FoxThisContext
+ 					put: (objectMemory followForwarded: (self frameContext: theFP))].
+ 			  oop := self frameMethod: theFP.
+ 			  (objectMemory isForwarded: oop) ifTrue:
+ 				[| newOop delta |
+ 				 newOop := objectMemory followForwarded: oop.
+ 				 theIPPtr ifNotNil:
+ 					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
+ 					 delta := newOop - oop.
+ 					 stackPages
+ 						longAt: theIPPtr
+ 						put: (stackPages longAt: theIPPtr) + delta].
+ 				stackPages
+ 					longAt: theFP + FoxMethod
+ 					put: (oop := newOop)].
+ 			  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 caller context."
+ 			 self assert: theFP = thePage baseFP.
+ 			 oop := self frameCallerContext: theFP.
+ 			 (objectMemory isForwarded: oop) ifTrue:
+ 				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was removed:
- ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
- followForwardingPointersInStackZone: theBecomeEffectsFlags
- 	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
- 	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
- 	 probe, since notionally objects' internals are accessed only via sending messages to them,
- 	 the exception is primitives that access the internals of the non-receiver argument(s).
- 
- 	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
- 	 the receivers (including the stacked receiver for non-local return) and method references
- 	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
- 	 scanning all of memory as in the old become."
- 	| 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 theFP callerFP offset oop |
- 		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]).
- 			  oop := stackPages longAt: theFP + FoxReceiver.
- 			  (objectMemory isOopForwarded: oop) ifTrue:
- 				[stackPages
- 					longAt: theFP + FoxReceiver
- 					put: (objectMemory followForwarded: oop)].
- 			  ((self frameHasContext: theFP)
- 			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
- 				[stackPages
- 					longAt: theFP + FoxThisContext
- 					put: (objectMemory followForwarded: (self frameContext: theFP))].
- 			  oop := self frameMethod: theFP.
- 			  (objectMemory isForwarded: oop) ifTrue:
- 				[| newOop delta |
- 				 newOop := objectMemory followForwarded: oop.
- 				 theIPPtr ifNotNil:
- 					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
- 					 delta := newOop - oop.
- 					 stackPages
- 						longAt: theIPPtr
- 						put: (stackPages longAt: theIPPtr) + delta].
- 				stackPages
- 					longAt: theFP + FoxMethod
- 					put: (oop := newOop)].
- 			  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 caller context."
- 			 self assert: theFP = thePage baseFP.
- 			 oop := self frameCallerContext: theFP.
- 			 (objectMemory isForwarded: oop) ifTrue:
- 				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: StackInterpreter>>spurPostBecomeAction: (in category 'object memory support') -----
  spurPostBecomeAction: theBecomeEffectsFlags
  	"Insulate the stack zone from the effects of a become.
  	 All receivers must be unfollowed for two reasons:
  		1. inst var access is direct with no read barrier
  		2. super sends (always to the receiver) have no class check and so don't trap
  		   for forwarded receivers.  This is an issue for primitives that assume their receiver
  		   is valid and don't validate.
  	 Super sends require an explicit check to ensure receivers in super sends are unforwarded.
  	 e.g. super doSomethingWith: (self become: other) forwards the receiver self pushed on the
  	 stack.  So we could avoid following non-pointer receivers.  But this is too tricky,  Instead, we
  	 always follow receivers.
  	 Methods must be unfollowed since bytecode access is direct with no read barrier.
  	 But this only needs to be done if the becomeEffectsFlags indicate that a
  	 CompiledMethod was becommed.
  	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
  	 that a pointer object was becommed."
  	<option: #SpurObjectMemory>
  	<inline: false> "For VM profiling"
  	self flushAtCache.
  	theBecomeEffectsFlags ~= 0 ifTrue:
  		[(theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
  			[self flushBecommedClassesInMethodCache].
  		 (theBecomeEffectsFlags anyMask: BecamePointerObjectFlag) ifTrue:
  			[self followForwardingPointersInScheduler.
  			 self followForwardingPointersInSpecialObjectsArray].
  		 (theBecomeEffectsFlags anyMask: BecamePointerObjectFlag + BecameCompiledMethodFlag) ifTrue:
  			[self followForwardingPointersInProfileState.
  			 (theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  				[self followForwardedMethodsInMethodCache.
  				 self followMethodNewMethodAndInstructionPointer]]].
+ 	self followForwardingPointersInStackZone!
- 	self followForwardingPointersInStackZone: theBecomeEffectsFlags!

Item was changed:
  ----- Method: VMBasicConstants class>>nonUnderscoreNamesDefinedAtCompileTime (in category 'C translation') -----
  nonUnderscoreNamesDefinedAtCompileTime
  	"Answer the set of names for variables that should be defined at compile time
  	 (excepting those that begin with underscore, which we assume are defined at compile time).
  	 Some of these get default values during simulation, and hence get defaulted in
  	 the various initializeMiscConstants methods.  But that they have values should
  	 /not/ cause the code generator to do dead code elimination based on their
  	 default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
  	 will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif.
  
  	And of course this is backwards.  We'd like to define names that are defined at translation time.
  	But doing so would entail defining (or referencing) hundreds of class and pool variables.  This way
  	is marginally more manageable."
  	^#(VMBIGENDIAN
  		IMMUTABILITY
  		STACKVM COGVM COGMTVM SPURVM
  		PharoVM								"Pharo vs Squeak"
+ 		TerfVM VM_TICKER					"Terf vs Squeak & Qwaq/Teleplace/Terf/Virtend high-priority thread support"
+ 		VMBenchmarks						"Primitives to measure the duration of fleeting operations"
- 		TerfVM VM_TICKER						"Terf vs Squeak & Qwaq/Teleplace/Terf high-priority thread support"
  		EnforceAccessControl					"Newspeak"
  		CheckRememberedInTrampoline		"IMMUTABILITY"
  		BIT_IDENTICAL_FLOATING_POINT PLATFORM_SPECIFIC_FLOATING_POINT	"Alternatives for using fdlibm for floating-point"
+ 		ITIMER_HEARTBEAT					"older linux's woultn't allow a higher priority thread, hence no threaded heartbeat."
- 		ITIMER_HEARTBEAT						"older linux's woultn't allow a higher priority thread, hence no threaded heartbeat."
  		TestingPrimitives
+ 		OBSOLETE_ALIEN_PRIMITIVES		"Ancient crap in the IA32ABI plugin"
- 		OBSOLETE_ALIEN_PRIMITIVES			"Ancient crap in the IA32ABI plugin"
  		LLDB									"As of lldb-370.0.42 Swift-3.1, passing function parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"
  		LRPCheck								"Optional checking for long running primitives"
  
  		"Plugin related"
  		SQUEAK_BUILTIN_PLUGIN
  		"ThreadedFFIPlugin related"
  		ALLOCA_LIES_SO_SETSP_BEFORE_CALL PLATFORM_API_USES_CALLEE_POPS_CONVENTION STACK_ALIGN_BYTES
  
+ 		"processor related; see ThreadedFFIPlugin & src/plugins/SqueakFFIPrims/SqueakFFIPrims.c"
- 		"processor related"
  		ARM32 ARM64
  		i386 i486 i586 i686 X86 I386
  		x86_64
  
  		"os related"
  		ACORN
  		EPLAN9
  		UNIX
  		WIN32
  		WIN64)!



More information about the Vm-dev mailing list