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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 9 19:08:43 UTC 2015


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

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

Name: VMMaker.oscog-eem.1178
Author: eem
Time: 9 April 2015, 12:07:00.341 pm
UUID: bb034bb1-371f-44a6-a66f-bbcfaff35456
Ancestors: VMMaker.oscog-tpr.1177

Implement Clément's much better solution for the
stale supersend problem.  Place code at the send
site for super sends to follow stale forwarded
receivers.  This parallels the interpreter implementation.

Beef up the post-become scan of send sites to
unlink all send sites that link to an invalid class tag.

=============== Diff against VMMaker.oscog-tpr.1177 ===============

Item was changed:
  ----- Method: CoInterpreter>>flushBecommedClassesInMethodZone (in category 'object memory support') -----
  flushBecommedClassesInMethodZone
  	<inline: true>
+ 	cogit unlinkSendsLinkedForInvalidClasses!
- 	cogit unlinkSendsToForwardedClasses!

Item was changed:
  ----- 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 inst var fetch we scan the receivers in the stack zone and follow
- 	 any forwarded ones.  This is way cheaper than scanning all of memory as in the old become.
  
+ 	 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"
- 	 Override to handle machine code frames, and to handle the lack of an explicit read barrier on super sends.
- 	 With most super send implementations (not Newspeak's absent super bytecodes) self, the receiver of the
- 	 super send, is pushed before any arguments.  So if self is becommed during argument marshalling, e.g.
- 		super doSomethingWith: (self become: self somethingElse)
- 	 then a stale forwarded reference to self could be left on the stack.  In the StackInterpreter we deal with this
- 	 with an explicit read barrier on supersend.  In the CoInterpreter we deal with it by following all non-argument
- 	 stack contents."
  	| theIPPtr |
  	<inline: false>
- 	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
- 	<var: #offset type: #'char *'>
- 	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
+ 	<var: #callerFP type: #'char *'>
+ 	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[theFP := thePage  headFP.
+ 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
- 			[theSP := thePage headSP.
- 			 theFP := thePage  headFP.
- 			 "Skip the instruction pointer on top of stack of inactive pages."
- 			 thePage = stackPage
- 				ifTrue: [theIPPtr := 0]
- 				ifFalse:
- 					[theIPPtr := theSP asUnsignedInteger.
- 					 theSP := theSP + objectMemory wordSize].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
- 			  offset := self frameReceiverLocation: theFP.
- 	 		  [theSP <= offset] whileTrue:
- 				[oop := stackPages longAt: theSP.
- 				 (objectMemory isOopForwarded: oop) ifTrue:
- 					[stackPages longAt: theSP put: (objectMemory followForwarded: 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))].
  			 (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]
- 					 oop := (self mframeHomeMethod: theFP) methodObject.
- 					 self assert: (objectMemory isForwarded: oop) 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 delta |
  						 newOop := objectMemory followForwarded: oop.
+ 						 offset := newOop - oop.
- 						 delta := newOop - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
+ 								put: (stackPages longAt: theIPPtr) + offset].
- 								put: (stackPages longAt: theIPPtr) + delta].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
+ 							put: (stackPages longAt: theFP + FoxIFSavedIP) + offset.
- 							put: (stackPages longAt: theFP + FoxIFSavedIP) + delta.
  						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.
- 				 theSP := self cCoerceSimple: theIPPtr + objectMemory wordSize to: #'char *'.
  				 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 changed:
  ----- Method: CoInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page.  Override to
  	 hold the caller context in a different place,  In the StackInterpreter we use
  	 the caller saved ip, but in the Cog VM caller saved ip is the ceBaseReturn:
  	 trampoline.  Simply hold the caller context in the first word of the stack."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	"theIP must be typed as signed because it is assigned ceCannotResumePC and so maybe implicitly typed as unsigned."
  	<var: #theIP type: #sqInt>
  	self assert: (objectMemory isContext: aContext).
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC signedIntFromLong < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	page := self newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory followObjField: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: aContext.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
+ 			[(objectMemory isForwarded: maybeClosure) ifTrue:
+ 				[maybeClosure := objectMemory fixFollowedField: ClosureIndex ofObject: aContext withInitialValue: maybeClosure].
+ 			 numArgs := self argumentCountOfClosure: maybeClosure.
- 			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  			 (theIP signedIntFromLong > 0
  			  and: [(self methodHeaderHasPrimitive: header)
  			  and: [theIP = (1 + (objectMemory lastPointerOfMethodHeader: header))]]) ifTrue:
  				[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: 0.
  	"N.B.  Don't set the baseFP, which marks the page as in use, until after
  	 ensureMethodIsCogged: and/or instructionPointer:forContext:frame:. These
  	 can cause a compiled code compaction which, if marked as in use, will
  	 examine this partially initialized page and crash."
  	page headFP: pointer.
  	"Create either a machine code frame or an interpreter frame based on the pc.  If the pc is -ve
  	 it is a machine code pc and so we produce a machine code frame.  If +ve an interpreter frame.
  	 N.B. Do *not* change this to try and map from a bytecode pc to a machine code frame under
  	 any circumstances.  See ensureContextIsExecutionSafeAfterAssignToStackPointer:"
  	theIP signedIntFromLong < 0
  		ifTrue:
  			[| cogMethod |
  			 "Since we would have to generate a machine-code method to be able to map
  			  the native pc anyway we should create a native method and native frame."
  			 cogMethod := self ensureMethodIsCogged: theMethod.
  			 theMethod := cogMethod asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
  					["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP = HasBeenReturnedFromMCPC signedIntFromLong
  						ifTrue:
  							[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
  												inHomeMethod: (self cCoerceSimple: theMethod
  																	to: #'CogMethod *')) asInteger.
  							 theMethod = 0 ifTrue:
  								[self error: 'cannot find machine code block matching closure''s startpc'].
  							 theIP := cogit ceCannotResumePC]
  						ifFalse:
  							[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
  							 theMethod := theMethod - ((theIP signedBitShift: -16) * cogit blockAlignment).
  							 theIP := theMethod - theIP signedIntFromShort].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag]
  				ifFalse:
  					[self assert: (theIP signedBitShift: -16) >= -1.
  					 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP := theIP = HasBeenReturnedFromMCPC signedIntFromLong
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: 0. "FoxIFSavedIP"
  			theIP := self iframeInstructionPointerForIndex: theIP method: theMethod].
  	page baseFP: page headFP.
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
- 	"Copy the non-argument temps and stack contents to the stack.
- 	 Follow these to avoid any stale self references from super sends."
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
+ 			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
- 			put: (objectMemory followField: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - objectMemory wordSize) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was changed:
  ----- Method: CogObjectRepresentation>>genEnsureOopInRegNotForwarded:scratchReg: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch
  	"Make sure that the oop in reg is not forwarded.  By default there is
  	 nothing to do.  Subclasses for memory managers that forward will override."
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch
+ 	"Make sure that the oop in reg is not forwarded.  This routine assumes the object will
+ 	 never be forwarded to an immediate, as it is used to unforward  literal variables (associations). 
+ 	 Use the fact that isForwardedObjectClassIndexPun is a power of two to save an instruction."
+ 	| skip loop ok |
+ 	<var: #ok type: #'AbstractInstruction *'>
+ 	<var: #skip type: #'AbstractInstruction *'>
- 	"Make sure that the oop in reg is not forwarded."
- 	| loop okImm okObj |
- 	<var: #okImm type: #'AbstractInstruction *'>
- 	<var: #okObj type: #'AbstractInstruction *'>
  	<var: #loop type: #'AbstractInstruction *'>
  	self assert: reg ~= scratch.
+ 	cogit MoveR: reg R: scratch.
+ 	skip := self genJumpImmediateInScratchReg: scratch.
+ 	loop := cogit Label.
- 	loop := cogit MoveR: reg R: scratch.
- 	okImm := self genJumpImmediateInScratchReg: scratch.
  	"notionally
  		self genGetClassIndexOfNonImm: reg into: scratch.
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  	 but the following is an instruction shorter:"
  	cogit MoveMw: 0 r: reg R: scratch.
  	cogit
  		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  		R: scratch.
+ 	ok := cogit JumpNonZero:  0.
- 	okObj := cogit JumpNonZero:  0.
  	self genLoadSlot: 0 sourceReg: reg destReg: reg.
  	cogit Jump: loop.
+ 	skip jmpTarget: (ok jmpTarget: cogit Label).
- 	okImm jmpTarget: (okObj jmpTarget: cogit Label).
  	^0!

Item was added:
+ ----- Method: Cogit>>annotationIsForUncheckedEntryPoint: (in category 'in-line cacheing') -----
+ annotationIsForUncheckedEntryPoint: annotation
+ 	<inline: true>
+ 	^annotation = IsSuperSend
+ 	  or: [BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]]!

Item was removed:
- ----- Method: Cogit>>unlinkIfForwardedSend:pc:ignored: (in category 'in-line cacheing') -----
- unlinkIfForwardedSend: annotation pc: mcpc ignored: superfluity
- 	<var: #mcpc type: #'char *'>
- 	<var: #nsSendCache type: #'NSSendCache *'>
- 	| entryPoint |
- 
- 	self cppIf: NewspeakVM ifTrue:
- 		[| nsSendCache |
- 		 annotation = IsNSSendCall ifTrue:
- 			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
- 			 (nsSendCache classTag ~= objectRepresentation illegalClassTag
- 			  and: [objectMemory isForwardedClassIndex: nsSendCache classTag]) ifTrue:
- 				[self voidNSSendCache: nsSendCache]].
- 			"Should we check if the enclosing object's class is forwarded as well?"
- 			^0 "keep scanning"].
- 
- 	(self isPureSendAnnotation: annotation) ifTrue:
- 		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 		 entryPoint > methodZoneBase
- 			ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
- 				[(objectMemory isForwardedClassIndex: (backEnd inlineCacheTagAt: mcpc asInteger)) ifTrue:
- 					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
- 						[:targetMethod :sendTable|
- 						 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
- 
- 	^0 "keep scanning"!

Item was added:
+ ----- Method: Cogit>>unlinkIfInvalidClassSend:pc:ignored: (in category 'in-line cacheing') -----
+ unlinkIfInvalidClassSend: annotation pc: mcpc ignored: superfluity
+ 	<var: #mcpc type: #'char *'>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	| entryPoint |
+ 
+ 	self cppIf: NewspeakVM ifTrue:
+ 		[| nsSendCache |
+ 		 annotation = IsNSSendCall ifTrue:
+ 			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 			 (nsSendCache classTag ~= objectRepresentation illegalClassTag
+ 			  and: [objectMemory isForwardedClassIndex: nsSendCache classTag]) ifTrue:
+ 				[self voidNSSendCache: nsSendCache]].
+ 			"Should we check if the enclosing object's class is forwarded as well?"
+ 			^0 "keep scanning"].
+ 
+ 	(self isPureSendAnnotation: annotation) ifTrue:
+ 		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 entryPoint > methodZoneBase ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
+ 			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 				[:targetMethod :sendTable|
+ 				 ((self annotationIsForUncheckedEntryPoint: annotation)
+ 				  or: [targetMethod cmType = CMOpenPIC]) ifFalse:
+ 					[(objectMemory isValidClassTag: (backEnd inlineCacheTagAt: mcpc asInteger)) ifFalse:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]]].
+ 
+ 	^0 "keep scanning"!

Item was added:
+ ----- Method: Cogit>>unlinkSendsLinkedForInvalidClasses (in category 'jit - api') -----
+ unlinkSendsLinkedForInvalidClasses
+ 	<api>
+ 	<option: #SpurObjectMemory>
+ 	"Unlink all sends in cog methods whose class tag is that of a forwarded class."
+ 	| cogMethod freedPIC |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	methodZoneBase ifNil: [^self].
+ 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	codeModified := freedPIC := false.
+ 	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod cmType = CMMethod
+ 			ifTrue:
+ 				[self mapFor: cogMethod
+ 					 performUntil: #unlinkIfInvalidClassSend:pc:ignored:
+ 					 arg: 0]
+ 			ifFalse:
+ 				[(cogMethod cmType = CMClosedPIC
+ 				  and: [self cPICHasForwardedClass: cogMethod]) ifTrue:
+ 					[methodZone freeMethod: cogMethod.
+ 					 freedPIC := true]].
+ 		cogMethod := methodZone methodAfter: cogMethod].
+ 	freedPIC
+ 		ifTrue: [self unlinkSendsToFree]
+ 		ifFalse:
+ 			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 				[processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]]!

Item was removed:
- ----- Method: Cogit>>unlinkSendsToForwardedClasses (in category 'jit - api') -----
- unlinkSendsToForwardedClasses
- 	<api>
- 	<option: #SpurObjectMemory>
- 	"Unlink all sends in cog methods whose class tag is that of a forwarded class."
- 	| cogMethod freedPIC |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	methodZoneBase ifNil: [^self].
- 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
- 	codeModified := freedPIC := false.
- 	[cogMethod < methodZone limitZony] whileTrue:
- 		[cogMethod cmType = CMMethod
- 			ifTrue:
- 				[self mapFor: cogMethod
- 					 performUntil: #unlinkIfForwardedSend:pc:ignored:
- 					 arg: 0]
- 			ifFalse:
- 				[(cogMethod cmType = CMClosedPIC
- 				  and: [self cPICHasForwardedClass: cogMethod]) ifTrue:
- 					[methodZone freeMethod: cogMethod.
- 					 freedPIC := true]].
- 		cogMethod := methodZone methodAfter: cogMethod].
- 	freedPIC
- 		ifTrue: [self unlinkSendsToFree]
- 		ifFalse:
- 			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
- 				[processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	self assert: (numArgs between: 0 and: 255). "say"
  	self assert: (objectMemory addressCouldBeOop: selector).
  	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
+ 	"Deal with stale super sends; see SpurMemoryManager's class comment."
+ 	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
+ 		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self annotate: (self MoveCw: tempOop R: TempReg) objRef: tempOop].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	self flag: 'currently caller pushes result'.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was added:
+ ----- Method: SpurMemoryManager>>isValidClassTag: (in category 'class table') -----
+ isValidClassTag: classIndex
+ 	<api>
+ 	| classOrNil |
+ 	self assert: (classIndex between: 0 and: 1 << self classIndexFieldWidth - 1).
+ 	classOrNil := self classOrNilAtIndex: classIndex.
+ 	^classOrNil ~= nilObj
+ 	 and: [(self rawHashBitsOf: classOrNil) = classIndex]!

Item was changed:
  ----- 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."
- 	 To avoid a read barrier on bytecode, literal and inst var fetch we scan the receivers and
- 	 methods 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>
- 	<var: #thePage type: #'StackPage *'>
- 	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
- 	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
+ 	<var: #callerFP type: #'char *'>
+ 	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
+ 		[:i| | thePage theFP callerFP ptr oop |
- 		[:i| | thePage theSP theFP callerFP theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[theFP := thePage  headFP.
- 			[theSP := thePage headSP.
- 			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
+ 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
- 			 thePage = stackPage
- 				ifTrue: [theIPPtr := 0]
- 				ifFalse:
- 					[theIPPtr := theSP asInteger.
- 					 theSP := theSP + objectMemory wordSize].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
- 			  theIP := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger. "reuse theIP; its just an offset here"
- 			  oop := stackPages longAt: theIP.
- 			  (objectMemory isOopForwarded: oop) ifTrue:
- 				[stackPages
- 					longAt: theIP
- 					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 ~= 0 ifTrue:
  					[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)].
+ 			  ptr := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger.
+ 			  oop := stackPages longAt: ptr.
+ 			  (objectMemory isOopForwarded: oop) ifTrue:
+ 				[stackPages
+ 					longAt: ptr
+ 					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asInteger.
  				 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>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	self assert: (objectMemory isContext: aContext).
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	page := self newStackPage.
  	pointer := page baseAddress.
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	(objectMemory isIntegerObject: theIP) ifFalse:
  		[self error: 'context is not resumable'].
  	theIP := objectMemory integerValueOf: theIP.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
+ 	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
- 	maybeClosure := objectMemory followField: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
+ 			[(objectMemory isForwarded: maybeClosure) ifTrue:
+ 				[maybeClosure := objectMemory fixFollowedField: ClosureIndex ofObject: aContext withInitialValue: maybeClosure].
+ 			 numArgs := self argumentCountOfClosure: maybeClosure.
- 			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  			 (theIP signedIntFromLong > 0
  			  and: [(self methodHeaderHasPrimitive: header)
  			  and: [theIP = (1 + (objectMemory lastPointerOfMethodHeader: header))]]) ifTrue:
  				[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)].
  			 stackPages longAt: pointer put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is sender context in base frame"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: (objectMemory followObjField: SenderIndex ofObject: aContext).
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: 0.
  	page baseFP: pointer; headFP: pointer.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: theMethod.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: aContext.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	theIP := self iframeInstructionPointerForIndex: theIP method: theMethod.
  	stackPages longAt: (pointer := pointer - objectMemory wordSize) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genMarshalledSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
+ 	"Deal with stale super sends; see SpurMemoryManager's class comment."
+ 	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
+ 		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self annotate: (self MoveCw: tempOop R: TempReg) objRef: tempOop].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list