[Vm-dev] VM Maker: VMMaker.oscog-rmacnak.1415.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 14 03:34:31 UTC 2015


Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1415.mcz

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

Name: VMMaker.oscog-rmacnak.1415
Author: rmacnak
Time: 13 July 2015, 8:33:03.418 pm
UUID: b80baa14-1f7b-43f2-aeee-f17c4262fdf8
Ancestors: VMMaker.oscog-tpr.1414

Compile Newspeak self and super sends as clean sends as well.

Slower in monomorphic case but net win for the larger benchmarks, presumably because it avoids I-cache flushes in the polymorphic case.

Also means implementing polymorphic caches for clean sends will benefit all non-ordinary sends.

DeltaBlue +8.2%
Splay +7.6%
ParserCombinators +4.7%
Richards +0.5%
SlotRead (replaced with self send) -17.6%

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

Item was added:
+ ----- Method: CoInterpreter>>ceDynamicSuperSend:receiver: (in category 'trampolines') -----
+ ceDynamicSuperSend: cacheAddress receiver: methodReceiver
+ 	"A dynamic super send cache missed."
+ 	| nsSendCache methodReceiverClassTag cogMethod errSelIdx |
+ 	<api>
+ 	<option: #NewspeakVM>
+ 	<inline: false>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 
+ 	cogit assertCStackWellAligned.
+ 	self assert: (objectMemory addressCouldBeOop: methodReceiver).
+ 	self deny: (objectMemory isOopForwarded: methodReceiver).
+ 
+ 	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
+ 	messageSelector := nsSendCache selector.
+ 	argumentCount := nsSendCache numArgs.
+ 	method := (self mframeHomeMethod: framePointer) methodObject.
+ 
+ 	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
+ 
+ 	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
+ 
+ 	(self
+ 		inlineLookupInNSMethodCacheSel: messageSelector
+ 		classTag: methodReceiverClassTag
+ 		method: method
+ 		lookupRule: LookupRuleDynamicSuper)
+ 			ifTrue:
+ 				[self assert: localAbsentReceiverOrZero = 0.
+ 				"check for coggability because method is in the cache"
+ 				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
+ 			ifFalse:
+ 				[self deny: (objectMemory isOopForwarded: messageSelector).
+ 				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
+ 				lkupClassTag := methodReceiverClassTag.
+ 				errSelIdx := self lookupDynamicSuperSendNoMNU: methodReceiver.
+ 				errSelIdx ~= 0 ifTrue:
+ 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self handleMNU: errSelIdx 
+ 						InMachineCodeTo: methodReceiver
+ 						classForMessage: (objectMemory classForClassTag: methodReceiverClassTag).
+ 					self unreachable].
+ 				self addNewMethodToNSCache: LookupRuleDynamicSuper].
+ 
+ 	(self maybeMethodHasCogMethod: newMethod) 
+ 		ifTrue: [
+ 			cogMethod := self cogMethodOf: newMethod.
+ 			cogMethod selector = objectMemory nilObject
+ 				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
+ 				ifFalse: ["Deal with anonymous accessors, e.g. in Newspeak.
+ 					The cogMethod may not have the
+ 					correct selector. If not, try and compile a new method
+ 					with the correct selector."
+ 					cogMethod selector ~= messageSelector ifTrue: [
+ 							(cogit cog: newMethod selector: messageSelector)
+ 								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
+ 			cogMethod selector = messageSelector
+ 				ifTrue:
+ 					[cogit
+ 						linkNSSendCache: nsSendCache 
+ 						classTag: methodReceiverClassTag
+ 						enclosingObject: 0
+ 						target: cogMethod
+ 						caller: self mframeHomeMethodExport]
+ 				ifFalse: ["Out of code memory. Fall through to interpret."].
+ 			instructionPointer := self popStack.
+ 			self executeNewMethod.
+ 			self unreachable].
+ 	instructionPointer := self popStack.
+ 	self interpretMethodFromMachineCode.
+ 	self unreachable.!

Item was removed:
- ----- Method: CoInterpreter>>ceDynamicSuperSend:to:numArgs: (in category 'trampolines') -----
- ceDynamicSuperSend: selector to: rcvr numArgs: numArgs
- 	"Entry-point for an unlinked dynamic super send in a CogMethod.  Smalltalk stack looks like
- 					receiver
- 					args
- 		head sp ->	sender return pc
- 		
- 	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
- 	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
- 	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
- 	because we're out of code memory.
- 
- 	Continue execution via either executeMethod or interpretMethodFromMachineCode:
- 	depending on whether the target method is cogged or not."
- 	<api>
- 	<option: #NewspeakVM>
- 	| classTag errSelIdx cogMethod |
- 	<inline: false>
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<var: #newCogMethod type: #'CogMethod *'>
- 
- 	cogit assertCStackWellAligned.
- 	self assert: (objectMemory addressCouldBeOop: rcvr).
- 	self sendBreakpoint: selector receiver: rcvr.
- 
- 	classTag := objectMemory fetchClassTagOf: rcvr.
- 	messageSelector := selector.
- 	argumentCount := numArgs.
- 	method := (self mframeHomeMethod: framePointer) methodObject.
- 
- 	(self
- 		inlineLookupInNSMethodCacheSel: messageSelector
- 		classTag: classTag
- 		method: method
- 		lookupRule: LookupRuleDynamicSuper)
- 			ifTrue:
- 				["check for coggability because method is in the cache"
- 				self
- 					ifAppropriateCompileToNativeCode: newMethod
- 					selector: selector]
- 			ifFalse:
- 				[(objectMemory isOopForwarded: selector) ifTrue:
- 					[self
- 						ceDynamicSuperSend: (self handleForwardedSelectorFaultFor: selector)
- 						to: rcvr
- 						numArgs: numArgs.
- 					self unreachable].
- 				 (objectMemory isForwardedClassTag: classTag) ifTrue:
- 					[self
- 						ceDynamicSuperSend: selector
- 						to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
- 						numArgs: numArgs.
- 					self unreachable].
- 				lkupClassTag := classTag.
- 				errSelIdx := self lookupDynamicSuperSendNoMNU: rcvr.
- 				errSelIdx ~= 0 ifTrue:
- 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
- 					self handleMNU: errSelIdx 
- 						InMachineCodeTo: rcvr
- 						classForMessage: (objectMemory classForClassTag: classTag).
- 					self unreachable].
- 				self addNewMethodToNSCache: LookupRuleSelf].
- 
- 	"Method found and has a cog method.  Attempt to link to it."
- 	(self maybeMethodHasCogMethod: newMethod) ifTrue:
- 		[cogMethod := self cogMethodOf: newMethod.
- 		 cogMethod selector = objectMemory nilObject
- 			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
- 			ifFalse:
- 				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
- 				  selector.  If not, try and compile a new method with the correct selector."
- 				 cogMethod selector ~= selector ifTrue:
- 					[(cogit cog: newMethod selector: selector) ifNotNil:
- 						[:newCogMethod| cogMethod := newCogMethod]]].
- 		 cogMethod selector = selector ifTrue:
- 			[cogit
- 				linkSendAt: (stackPages longAt: stackPointer)
- 				in: (self mframeHomeMethod: framePointer)
- 				to: cogMethod
- 				offset: cogit entryOffset
- 				receiver: rcvr].
- 		 instructionPointer := self popStack.
- 		 self executeNewMethod.
- 		 self unreachable].
- 	instructionPointer := self popStack.
- 	self interpretMethodFromMachineCode.
- 	self unreachable.!

Item was added:
+ ----- Method: CoInterpreter>>ceSelfSend:receiver: (in category 'trampolines') -----
+ ceSelfSend: cacheAddress receiver: methodReceiver
+ 	"A self send cache missed."
+ 	| nsSendCache methodReceiverClassTag cogMethod errSelIdx |
+ 	<api>
+ 	<option: #NewspeakVM>
+ 	<inline: false>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 
+ 	cogit assertCStackWellAligned.
+ 	self assert: (objectMemory addressCouldBeOop: methodReceiver).
+ 	self deny: (objectMemory isOopForwarded: methodReceiver).
+ 
+ 	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
+ 	messageSelector := nsSendCache selector.
+ 	argumentCount := nsSendCache numArgs.
+ 	method := (self mframeHomeMethod: framePointer) methodObject.
+ 
+ 	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
+ 
+ 	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
+ 
+ 	(self
+ 		inlineLookupInNSMethodCacheSel: messageSelector
+ 		classTag: methodReceiverClassTag
+ 		method: method
+ 		lookupRule: LookupRuleSelf)
+ 			ifTrue:
+ 				[self assert: localAbsentReceiverOrZero = 0.
+ 				"check for coggability because method is in the cache"
+ 				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
+ 			ifFalse:
+ 				[self deny: (objectMemory isOopForwarded: messageSelector).
+ 				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
+ 				lkupClassTag := methodReceiverClassTag.
+ 				errSelIdx := self lookupOuterSendNoMNU: methodReceiver depth: 0.
+ 				errSelIdx ~= 0 ifTrue:
+ 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self handleMNU: errSelIdx 
+ 						InMachineCodeTo: methodReceiver
+ 						classForMessage: (objectMemory classForClassTag: methodReceiverClassTag).
+ 					self unreachable].
+ 				self addNewMethodToNSCache: LookupRuleSelf].
+ 
+ 	(self maybeMethodHasCogMethod: newMethod) 
+ 		ifTrue: [
+ 			cogMethod := self cogMethodOf: newMethod.
+ 			cogMethod selector = objectMemory nilObject
+ 				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
+ 				ifFalse: ["Deal with anonymous accessors, e.g. in Newspeak.
+ 					The cogMethod may not have the
+ 					correct selector. If not, try and compile a new method
+ 					with the correct selector."
+ 					cogMethod selector ~= messageSelector ifTrue: [
+ 							(cogit cog: newMethod selector: messageSelector)
+ 								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
+ 			cogMethod selector = messageSelector
+ 				ifTrue:
+ 					[cogit
+ 						linkNSSendCache: nsSendCache 
+ 						classTag: methodReceiverClassTag
+ 						enclosingObject: 0
+ 						target: cogMethod
+ 						caller: self mframeHomeMethodExport]
+ 				ifFalse: ["Out of code memory. Fall through to interpret."].
+ 			instructionPointer := self popStack.
+ 			self executeNewMethod.
+ 			self unreachable].
+ 	instructionPointer := self popStack.
+ 	self interpretMethodFromMachineCode.
+ 	self unreachable.!

Item was removed:
- ----- Method: CoInterpreter>>ceSelfSend:to:numArgs: (in category 'trampolines') -----
- ceSelfSend: selector to: rcvr numArgs: numArgs
- 	"Entry-point for an unlinked self send in a CogMethod.  Smalltalk stack looks like
- 					receiver
- 					args
- 		head sp ->	sender return pc
- 		
- 	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
- 	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
- 	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
- 	because we're out of code memory.
- 
- 	Continue execution via either executeMethod or interpretMethodFromMachineCode:
- 	depending on whether the target method is cogged or not."
- 	<api>
- 	<option: #NewspeakVM>
- 	| classTag errSelIdx cogMethod |
- 	<inline: false>
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<var: #newCogMethod type: #'CogMethod *'>
- 
- 	cogit assertCStackWellAligned.
- 	self assert: (objectMemory addressCouldBeOop: rcvr).
- 	self sendBreakpoint: selector receiver: rcvr.
- 
- 	classTag := objectMemory fetchClassTagOf: rcvr.
- 	messageSelector := selector.
- 	argumentCount := numArgs.
- 	method := (self mframeHomeMethod: framePointer) methodObject.
- 
- 	(self
- 		inlineLookupInNSMethodCacheSel: messageSelector
- 		classTag: classTag
- 		method: method
- 		lookupRule: LookupRuleSelf)
- 			ifTrue:
- 				["check for coggability because method is in the cache"
- 				self
- 					ifAppropriateCompileToNativeCode: newMethod
- 					selector: selector]
- 			ifFalse:
- 				[(objectMemory isOopForwarded: selector) ifTrue:
- 					[self
- 						ceSelfSend: (self handleForwardedSelectorFaultFor: selector)
- 						to: rcvr
- 						numArgs: numArgs.
- 					self unreachable].
- 			 	(objectMemory isForwardedClassTag: classTag) ifTrue:
- 					[self
- 						ceSelfSend: selector
- 						to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
- 						numArgs: numArgs.
- 					self unreachable].
- 				lkupClassTag := classTag.
- 				errSelIdx := self lookupOuterSendNoMNU: rcvr depth: 0.
- 				errSelIdx ~= 0 ifTrue:
- 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
- 					self handleMNU: errSelIdx 
- 						InMachineCodeTo: rcvr
- 						classForMessage: (objectMemory classForClassTag: classTag).
- 					self unreachable].
- 				self addNewMethodToNSCache: LookupRuleSelf].
- 
- 	"Method found and has a cog method.  Attempt to link to it."
- 	(self maybeMethodHasCogMethod: newMethod) ifTrue:
- 		[cogMethod := self cogMethodOf: newMethod.
- 		 cogMethod selector = objectMemory nilObject
- 			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
- 			ifFalse:
- 				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
- 				  selector.  If not, try and compile a new method with the correct selector."
- 				 cogMethod selector ~= selector ifTrue:
- 					[(cogit cog: newMethod selector: selector) ifNotNil:
- 						[:newCogMethod| cogMethod := newCogMethod]]].
- 		 cogMethod selector = selector ifTrue:
- 			[cogit
- 				linkSendAt: (stackPages longAt: stackPointer)
- 				in: (self mframeHomeMethod: framePointer)
- 				to: cogMethod
- 				offset: cogit entryOffset
- 				receiver: rcvr].
- 		 instructionPointer := self popStack.
- 		 self executeNewMethod.
- 		 self unreachable].
- 	instructionPointer := self popStack.
- 	self interpretMethodFromMachineCode.
- 	self unreachable.!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #callerMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
- 	self cppIf: NewspeakVM ifTrue:
- 		[| callerMethod annotation |
- 		 self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
- 		 callerMethod := coInterpreter mframeHomeMethod: coInterpreter getFramePointer.
- 		 self assert: (outerReturn
- 						between: callerMethod asUnsignedInteger + cmNoCheckEntryOffset
- 						and: callerMethod asUnsignedInteger + callerMethod blockSize).
- 		 annotation := self annotationForMcpc: outerReturn in: callerMethod.
- 		 self assert: annotation >= IsSendCall.
- 		 "Avoid the effort of implementing PICs for the relatively high dynamic frequency
- 		  self send and simply rebind the send site (for now)."
- 		 annotation = IsNSSelfSend ifTrue:
- 			[coInterpreter
- 				ceSelfSend: targetMethod selector
- 				to: receiver
- 				numArgs: targetMethod cmNumArgs.
- 			self unreachable].
- 		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
- 		  dynamic super send and simply rebind the send site."
- 		 annotation = IsNSDynamicSuperSend ifTrue:
- 			[coInterpreter
- 				ceDynamicSuperSend: targetMethod selector
- 				to: receiver
- 				numArgs: targetMethod cmNumArgs.
- 			self unreachable]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  	processor flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was removed:
- ----- Method: Cogit>>genNSSendTrampolineFor:numArgs:called: (in category 'initialization') -----
- genNSSendTrampolineFor: aRoutine numArgs: numArgs called: aString
- 	"ReceiverResultReg: method receiver
- 	SendNumArgsReg: the NSSendCache cache"
- 	<option: #NewspeakVM>
- 	<var: #aRoutine type: #'void *'>
- 	<var: #aString type: #'char *'>
- 	| jumpMiss jumpItsTheReceiverStupid |
- 	<var: #jumpMiss type: #'AbstractInstruction *'>
- 	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
- 	self zeroOpcodeIndex.
- 	objectRepresentation
- 		genGetInlineCacheClassTagFrom: ReceiverResultReg
- 		into: ClassReg
- 		forEntry: false.
- 	self MoveMw: NSCClassTagIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
- 	self CmpR: ClassReg R: TempReg.
- 	jumpMiss := self JumpNonZero: 0.
- 	self MoveMw: NSCEnclosingObjectIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
- 	self CmpCq: 0 R: TempReg.
- 	jumpItsTheReceiverStupid := self JumpZero: 0.
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	"Now set the stacked receiver, if needed.  If there are reg args this is
- 	 not required; see genPushRegisterArgsForNumArgs:numArgs: below."
- 	(self numRegArgs = 0 or: [numArgs > self numRegArgs]) ifTrue:
- 		[numArgs >= (NumSendTrampolines - 1)
- 			ifTrue: "arbitrary argument count"
- 				[self MoveMw: NSCNumArgsIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
- 				 backEnd hasLinkRegister ifFalse:
- 					[self AddCq: 1 R: TempReg]..
- 				 self MoveR: ReceiverResultReg Xwr: TempReg R: SPReg]
- 			ifFalse: "Known argument count"
- 				[self MoveR: TempReg Mw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]) + numArgs * objectMemory wordSize r: SPReg]].
- 	jumpItsTheReceiverStupid jmpTarget: self Label.
- 	self MoveMw: NSCTargetIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
- 	self JumpR: TempReg.
- 
- 	jumpMiss jmpTarget: self Label.
- 	objectRepresentation
- 		genEnsureOopInRegNotForwarded: ReceiverResultReg
- 		scratchReg: TempReg
- 		updatingMw: FoxMFReceiver
- 		r: FPReg.
- 	self numRegArgs > 0 ifTrue:
- 		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: TempReg].
- 	^self
- 		genTrampolineFor: aRoutine
- 		called: aString
- 		numArgs: 2
- 		arg: SendNumArgsReg "The NSSendCache"
- 		arg: ReceiverResultReg
- 		arg: nil
- 		arg: nil
- 		saveRegs: false
- 		pushLinkReg: true
- 		resultReg: ReceiverResultReg  "Never happens?"
- 		appendOpcodes: true!

Item was added:
+ ----- Method: Cogit>>genNSSendTrampolineFor:numArgs:enclosingObjectCheck:called: (in category 'initialization') -----
+ genNSSendTrampolineFor: aRoutine numArgs: numArgs enclosingObjectCheck: eoCheckFlag called: aString
+ 	"ReceiverResultReg: method receiver
+ 	SendNumArgsReg: the NSSendCache cache"
+ 	<option: #NewspeakVM>
+ 	<var: #aRoutine type: #'void *'>
+ 	<var: #aString type: #'char *'>
+ 	| jumpMiss jumpItsTheReceiverStupid |
+ 	<var: #jumpMiss type: #'AbstractInstruction *'>
+ 	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
+ 	self zeroOpcodeIndex.
+ 	objectRepresentation
+ 		genGetInlineCacheClassTagFrom: ReceiverResultReg
+ 		into: ClassReg
+ 		forEntry: false.
+ 	self MoveMw: NSCClassTagIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
+ 	self CmpR: ClassReg R: TempReg.
+ 	jumpMiss := self JumpNonZero: 0.
+ 
+ 	eoCheckFlag ifTrue:
+ 		[self MoveMw: NSCEnclosingObjectIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
+ 		self CmpCq: 0 R: TempReg.
+ 		jumpItsTheReceiverStupid := self JumpZero: 0.
+ 		self MoveR: TempReg R: ReceiverResultReg.
+ 		"Now set the stacked receiver, if needed.  If there are reg args this is
+ 		 not required; see genPushRegisterArgsForNumArgs:numArgs: below."
+ 		(self numRegArgs = 0 or: [numArgs > self numRegArgs]) ifTrue:
+ 			[numArgs >= (NumSendTrampolines - 1)
+ 				ifTrue: "arbitrary argument count"
+ 					[self MoveMw: NSCNumArgsIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
+ 					 backEnd hasLinkRegister ifFalse:
+ 						[self AddCq: 1 R: TempReg]..
+ 					 self MoveR: ReceiverResultReg Xwr: TempReg R: SPReg]
+ 				ifFalse: "Known argument count"
+ 					[self MoveR: TempReg Mw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]) + numArgs * objectMemory wordSize r: SPReg]].
+ 		jumpItsTheReceiverStupid jmpTarget: self Label].
+ 
+ 	self MoveMw: NSCTargetIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
+ 	self JumpR: TempReg.
+ 
+ 	jumpMiss jmpTarget: self Label.
+ 	objectRepresentation
+ 		genEnsureOopInRegNotForwarded: ReceiverResultReg
+ 		scratchReg: TempReg
+ 		updatingMw: FoxMFReceiver
+ 		r: FPReg.
+ 	self numRegArgs > 0 ifTrue:
+ 		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: TempReg].
+ 	^self
+ 		genTrampolineFor: aRoutine
+ 		called: aString
+ 		numArgs: 2
+ 		arg: SendNumArgsReg "The NSSendCache"
+ 		arg: ReceiverResultReg
+ 		arg: nil
+ 		arg: nil
+ 		saveRegs: false
+ 		pushLinkReg: true
+ 		resultReg: nil
+ 		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>generateNewspeakSendTrampolines (in category 'initialization') -----
  generateNewspeakSendTrampolines
  	"Self send, dynamic super send, implicit receiver send, and outer send"
  	<option: #NewspeakVM>
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		selfSendTrampolines
  			at: numArgs
+ 			put: (self 
+ 				genNSSendTrampolineFor: #ceSelfSend:receiver:
+ 				numArgs: numArgs enclosingObjectCheck: false
+ 				called: (self trampolineName: 'ceSelfSend' numArgs: numArgs))].
- 			put: (self genTrampolineFor: #ceSelfSend:to:numArgs:
- 					  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
- 					  arg: ClassReg
- 					  arg: ReceiverResultReg
- 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		dynamicSuperSendTrampolines
  			at: numArgs
+ 			put: (self 
+ 				genNSSendTrampolineFor: #ceDynamicSuperSend:receiver:
+ 				numArgs: numArgs enclosingObjectCheck: false
+ 				called: (self trampolineName: 'ceDynamicSuperSend' numArgs: numArgs))].
- 			put: (self genTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 					  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
- 					  arg: ClassReg
- 					  arg: ReceiverResultReg
- 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		implicitReceiverSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
+ 				numArgs: numArgs enclosingObjectCheck: true
- 				numArgs: numArgs
  				called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: numArgs))].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		outerSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceOuterSend:receiver:
+ 				numArgs: numArgs enclosingObjectCheck: true
- 				numArgs: numArgs
  				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))].
  
  !

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode)
  		(1  79   79 genPushConstantOneBytecode)
  
  		(1   80 101 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
  		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
+ 		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped hasIRC)
- 		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
+ 		(2 245 245 genExtSendAbsentSelfBytecode isMapped hasIRC)
- 		(2 245 245 genExtSendAbsentSelfBytecode isMapped)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254 genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genNSSend:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genNSSend: selector numArgs: numArgs depth: depth sendTable: sendTable
+ 	<var: #sendTable type: #'sqInt *'>
+ 	| nsSendCache |
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 
+ 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
+ 	indexOfIRC := indexOfIRC + 1.
+ 	self assert: (objectMemory isInOldSpace: nsSendCache).
+ 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
+ 
+ 	"This leaves the method receiver on the stack, which might not be the implicit receiver.
+ 	 But the lookup trampoline will establish the on-stack receiver once it locates it."
+ 	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	self PushR: ReceiverResultReg.
+ 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genSendAbsentDynamicSuper: selector numArgs: numArgs
  	<inline: false>
+ 	^self
+ 		genNSSend: selector
+ 		numArgs: numArgs
+ 		depth: LookupRuleDynamicSuper
+ 		sendTable: dynamicSuperSendTrampolines!
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 	^self genSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
  genSendAbsentImplicit: selector numArgs: numArgs
  	<inline: false>
  	^self
+ 		genNSSend: selector
- 		genSendAbsentImplicitOrOuter: selector
  		numArgs: numArgs
+ 		depth: LookupRuleImplicit
- 		depth: 255 "Unused"
  		sendTable: implicitReceiverSendTrampolines!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
- genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
- 	<var: #sendTable type: #'sqInt *'>
- 	| nsSendCache |
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 
- 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
- 	indexOfIRC := indexOfIRC + 1.
- 	self assert: (objectMemory isInOldSpace: nsSendCache).
- 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
- 
- 	"This leaves the method receiver on the stack, which might not be the implicit receiver.
- 	 But the lookup trampoline will establish the on-stack receiver once it locates it."
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 
- 	"Load the cache last so it is a fixed distance from the call."
- 	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
- 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
- 
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentOuter:numArgs:depth: (in category 'bytecode generators') -----
  genSendAbsentOuter: selector numArgs: numArgs depth: depth
  	<inline: false>
  	^self
+ 		genNSSend: selector
- 		genSendAbsentImplicitOrOuter: selector
  		numArgs: numArgs
  		depth: depth
  		sendTable: outerSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentSelf:numArgs: (in category 'bytecode generators') -----
  genSendAbsentSelf: selector numArgs: numArgs
  	<inline: false>
+ 	^self
+ 		genNSSend: selector
+ 		numArgs: numArgs
+ 		depth: LookupRuleSelf
+ 		sendTable: selfSendTrampolines!
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 	^self genSend: selector numArgs: numArgs sendTable: selfSendTrampolines!

Item was changed:
  ----- Method: StackInterpreter>>lookupDynamicSuperSend (in category 'message sending') -----
  lookupDynamicSuperSend
  	"Do the full lookup for a Newspeak super send.
  	IN: messageSelector
  	IN: argumentCount
  	OUT: localAbsentReceiver
  	OUT: newMethod
  	OUT: primitiveIndex
  	RESULT: LookupRuleDynamicSuper or LookupRuleMNU"
  
  	| methodMixin methodMixinApplication |
  	localAbsentReceiver := self receiver.
+ 	localAbsentReceiverOrZero := 0.
  	methodMixin := self methodClassOf: method.
  	methodMixinApplication := self
  		findApplicationOfTargetMixin: methodMixin
  		startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
  	lkupClass := self superclassOf: methodMixinApplication. "For use by MNU"
  	^self lookupProtected: messageSelector startingAt: lkupClass rule: LookupRuleDynamicSuper!

Item was changed:
  ----- Method: StackInterpreter>>lookupDynamicSuperSendNoMNU: (in category 'message sending') -----
  lookupDynamicSuperSendNoMNU: methodReceiver
  	"Do the full lookup for a Newspeak super send.
  	IN: messageSelector
  	IN: argumentCount
  	OUT: localAbsentReceiver
  	OUT: newMethod
  	OUT: primitiveIndex
  	RESULT: 0 or SelectorDoesNotUnderstand"
  
  	| methodMixin methodMixinApplication |
  	localAbsentReceiver := methodReceiver.
+ 	localAbsentReceiverOrZero := 0.
  	methodMixin := self methodClassOf: method.
  	methodMixinApplication := self
  		findApplicationOfTargetMixin: methodMixin
  		startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
  	lkupClass := self superclassOf: methodMixinApplication. "For use by MNU"
  	^self lookupProtectedNoMNU: messageSelector startingAt: lkupClass rule: LookupRuleDynamicSuper!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:numInitialNils:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode needsFrameIfExtBGT2: 1)
  		(1  78   78 genPushConstantZeroBytecode needsFrameNever: 1)
  		(1  79   79 genPushConstantOneBytecode needsFrameNever: 1)
  
  		(1   80   80 genSpecialSelectorArithmetic isMapped AddRR)
  		(1   81   81 genSpecialSelectorArithmetic isMapped SubRR)
  		(1   82   82 genSpecialSelectorComparison isMapped JumpLess)
  		(1   83   83 genSpecialSelectorComparison isMapped JumpGreater)
  		(1   84   84 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1   85   85 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1   86   86 genSpecialSelectorComparison isMapped JumpZero)
  		(1   87   87 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1   88   93 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1   94   94 genSpecialSelectorArithmetic isMapped AndRR)
  		(1   95   95 genSpecialSelectorArithmetic isMapped OrRR)
  		(1   96 101 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
  		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension					needsFrameNever: 0)
  		(2 225 225 extBBytecode extension					needsFrameNever: 0)
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
+ 		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped hasIRC)
- 		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
+ 		(2 245 245	genExtSendAbsentSelfBytecode isMapped hasIRC)
- 		(2 245 245	genExtSendAbsentSelfBytecode isMapped)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254	genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genNSSend:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genNSSend: selector numArgs: numArgs depth: depth sendTable: sendTable
+ 	<var: #sendTable type: #'sqInt *'>
+ 	| nsSendCache |
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 
+ 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
+ 	indexOfIRC := indexOfIRC + 1.
+ 	self assert: (objectMemory isInOldSpace: nsSendCache).
+ 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
+ 
+ 	self ssAllocateCallReg: SendNumArgsReg.
+ 
+ 	"This may leave the method receiver on the stack, which might not be the implicit receiver.
+ 	 But the lookup trampoline will establish an on-stack receiver once it locates it."
+ 	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	optStatus isReceiverResultRegLive: false.
+ 	self ssPushRegister: ReceiverResultReg.
+ 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generators') -----
- genSendAbsentDynamicSuper: selector numArgs: numArgs
- 	<inline: false>
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
- genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
- 	<var: #sendTable type: #'sqInt *'>
- 	| nsSendCache |
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 
- 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
- 	indexOfIRC := indexOfIRC + 1.
- 	self assert: (objectMemory isInOldSpace: nsSendCache).
- 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
- 
- 	self ssAllocateCallReg: SendNumArgsReg.
- 
- 	"This may leave the method receiver on the stack, which might not be the implicit receiver.
- 	 But the lookup trampoline will establish an on-stack receiver once it locates it."
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 
- 	"Load the cache last so it is a fixed distance from the call."
- 	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
- 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
- 
- 	optStatus isReceiverResultRegLive: false.
- 	self ssPushRegister: ReceiverResultReg.
- 	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSendAbsentSelf:numArgs: (in category 'bytecode generators') -----
- genSendAbsentSelf: selector numArgs: numArgs
- 	<inline: false>
- 	self marshallAbsentReceiverSendArguments: numArgs.
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: selfSendTrampolines!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>generateNewspeakSendTrampolines (in category 'initialization') -----
- generateNewspeakSendTrampolines
- 	"Self send, dynamic super send, implicit receiver send, and outer send."
- 	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
- 	<option: #NewspeakVM>
- 	0 to: NumSendTrampolines - 1 do:
- 		[:numArgs|
- 		selfSendTrampolines
- 			at: numArgs
- 			put: (self genSendTrampolineFor: #ceSelfSend:to:numArgs:
- 					  numArgs: numArgs
- 					  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
- 					  arg: ClassReg
- 					  arg: ReceiverResultReg
- 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 
- 	0 to: NumSendTrampolines - 1 do:
- 		[:numArgs|
- 		dynamicSuperSendTrampolines
- 			at: numArgs
- 			put: (self genSendTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 					  numArgs: numArgs
- 					  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
- 					  arg: ClassReg
- 					  arg: ReceiverResultReg
- 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 
- 	0 to: NumSendTrampolines - 1 do:
- 		[:numArgs|
- 		implicitReceiverSendTrampolines
- 			at: numArgs
- 			put: (self 
- 				genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
- 				numArgs: numArgs
- 				called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: numArgs))].
- 
- 	0 to: NumSendTrampolines - 1 do:
- 		[:numArgs|
- 		outerSendTrampolines
- 			at: numArgs
- 			put: (self 
- 				genNSSendTrampolineFor: #ceOuterSend:receiver:
- 				numArgs: numArgs
- 				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))]!



More information about the Vm-dev mailing list