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

commits at source.squeak.org commits at source.squeak.org
Sat Jul 18 20:03:09 UTC 2015


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

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

Name: VMMaker.oscog-eem.1425
Author: eem
Time: 18 July 2015, 1:01:15.695 pm
UUID: 940a2af5-eb00-4257-8328-aba1f471da49
Ancestors: VMMaker.oscog-eem.1424

Don't use cppIf: NewspeakVM(et al)  to avoid leaving #if NewspeakVM everywhere.  Instead rely on generation-time dead code removal.  Both Newspeak and Saqueak VMs benefit from improved readability.

Fix some primitiveFail[For:] calls in potential mirror primitives that did not return after falure, and could hence continue to do damage after detecting a failure condition.

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

Item was changed:
  ----- Method: CoInterpreter>>internalFindNewMethodOrdinary (in category 'message sending') -----
  internalFindNewMethodOrdinary
  	"Find the compiled method to be run when the current messageSelector is
  	 sent to the given class, setting the values of newMethod and primitiveIndex."
  	| ok |
  	<inline: true>
  	ok := self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
  			[self externalizeIPandSP.
  			 ((objectMemory isOopForwarded: messageSelector)
  			  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
  				[(objectMemory isOopForwarded: messageSelector) ifTrue:
  					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  				 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
  					[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
  				(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
  					[^self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]].
  			lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 			NewspeakVM
- 			self cppIf: #NewspeakVM
  				ifTrue: [self lookupOrdinarySend]
  				ifFalse: [self lookupMethodInClass: lkupClass].
  			self internalizeIPandSP.
  			self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: CoInterpreter>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
  validInstructionPointer: instrPointer inMethod: aMethod framePointer: fp
  	<var: #instrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
  	<var: #fp type: #'char *'>
  	| theInstrPointer cogMethod |
  	<var: #theInstrPointer type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
  	instrPointer = cogit ceCannotResumePC ifTrue:
  		[^self isMachineCodeFrame: fp].
  	instrPointer = cogit ceReturnToInterpreterPC
  		ifTrue:
  			[(self isMachineCodeFrame: fp) ifTrue:
  				[^false].
  			 theInstrPointer := self iframeSavedIP: fp]
  		ifFalse:
  			[theInstrPointer := instrPointer.
+ 			 NewspeakVM
- 			self cppIf: NewspeakVM
  				ifTrue:
  					[(self isMachineCodeFrame: fp) ifTrue:
  						[cogMethod := self mframeHomeMethod: fp.
  						 ^theInstrPointer >= (cogMethod asUnsignedInteger + (cogit sizeof: CogMethod))
  						   and: [theInstrPointer < (cogMethod asUnsignedInteger + cogMethod blockSize)]]]
  				ifFalse:
  					[| header |
  					 header := self rawHeaderOf: aMethod.
  					 ((self isCogMethodReference: header)
  					   and: [theInstrPointer < objectMemory startOfMemory]) ifTrue:
  					 	[cogMethod := self cCoerceSimple: header to: #'CogMethod *'.
  					 	 ^theInstrPointer >= (header + (cogit sizeof: CogMethod))
  					 	 and: [theInstrPointer < (header + cogMethod blockSize)]]]].
  	^super validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp!

Item was changed:
  ----- Method: CogMethodZone>>clearCogCompiledCode (in category 'jit - api') -----
  clearCogCompiledCode
  	"Free all methods"
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	NewspeakVM ifTrue: [unpairedMethodList := nil].
- 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[self freeMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod].
  	self manageFrom: baseAddress to: limitAddress!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
  	| objectHeaderValue source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	openPICList := nil.
  	methodCount := 0.
+ 	NewspeakVM ifTrue: [unpairedMethodList := nil].
- 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
+ 		 NewspeakVM ifTrue:
- 		 self cppIf: NewspeakVM ifTrue:
  				[(source cmType = CMMethod
  				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
  					[source nextMethodOrIRCs: unpairedMethodList.
  					 unpairedMethodList := source asUnsignedInteger]].
  		 SistaVM ifTrue:
  			[self clearSavedPICUsageCount: source].
  		 source cmType = CMOpenPIC ifTrue:
  			[source nextOpenPIC: openPICList asUnsignedInteger.
  			 openPICList := source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 objectMemory mem: dest mo: source ve: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
  					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
+ 							 NewspeakVM ifTrue:
- 							 self cppIf: NewspeakVM ifTrue:
  								[dest nextMethodOrIRCs: unpairedMethodList.
  								 unpairedMethodList := dest asUnsignedInteger]]]
  				ifFalse:
  					[SistaVM ifTrue:
  						[self clearSavedPICUsageCount: dest].
  					dest cmType = CMOpenPIC ifTrue:
  						[dest nextOpenPIC: openPICList asUnsignedInteger.
  						 openPICList := dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter
  								cCoerceSimple: dest asUnsignedInteger + bytes
  								to: #'CogMethod *'].
  		 source := coInterpreter
  							cCoerceSimple: source asUnsignedInteger + bytes
  							to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: ((cogit cogMethodDoesntLookKosher: cogMethod) = 0
  				 or: [(cogit cogMethodDoesntLookKosher: cogMethod) = 23
  					 and: [(cogit cCoerceSimple: cogMethod methodObject to: #'CogMethod *') cmType = CMFree]]).
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
+ 				 NewspeakVM ifTrue:
- 				 self cppIf: NewspeakVM ifTrue:
  					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
+ 				 NewspeakVM ifTrue:
- 				 self cppIf: NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod].
  	cogMethod cmRefersToYoung: false.
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>manageFrom:to: (in category 'initialization') -----
  manageFrom: theStartAddress to: theLimitAddress
  	<returnTypeC: #void>
  	mzFreeStart := baseAddress := theStartAddress.
  	youngReferrers := limitAddress := theLimitAddress.
  	openPICList := nil.
+ 	NewspeakVM ifTrue: [unpairedMethodList := nil].
- 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	methodBytesFreedSinceLastCompaction := 0.
  	methodCount := 0!

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache enclosingObject |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			[(objectRepresentation checkValidOopReference: nsSendCache selector) ifFalse:
  				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  				^1]].
  			(enclosingObject := nsSendCache enclosingObject) ~= 0 ifTrue:
  				[[(objectRepresentation checkValidOopReference: enclosingObject) ifFalse:
  					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
  					into: [:off :table| offset := off]].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
  		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation validInlineCacheTag: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]
  			ifFalse: "unlinked send or super send; cacheTag is a selector"
  				[(objectRepresentation checkValidOopReference: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal entryPoint |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (self asserta: (objectRepresentation checkValidOopReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache classTag enclosingObject nsTargetMethod |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(self asserta: (objectRepresentation checkValidOopReference: nsSendCache selector)) ifFalse:
  				[^9].
  			classTag := nsSendCache classTag.
  			(self asserta: (classTag = 0 or: [objectRepresentation validInlineCacheTag: classTag])) ifFalse:
  				[^10].
  			enclosingObject := nsSendCache enclosingObject.
  			(self asserta: (enclosingObject = 0 or: [objectRepresentation checkValidOopReference: enclosingObject])) ifFalse:
  				[^11].
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: [
  				nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(self asserta: (nsTargetMethod cmType = CMMethod)) ifFalse:
  					[^12]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:offset :cacheTag :tagCouldBeObject|
  			tagCouldBeObject
  				ifTrue:
  					[(objectRepresentation couldBeObject: cacheTag)
  						ifTrue:
  							[(self asserta: (objectRepresentation checkValidOopReference: cacheTag)) ifFalse:
  								[^4]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^5]].
  					((objectRepresentation couldBeObject: cacheTag)
  					 and: [objectMemory isReallyYoungObject: cacheTag]) ifTrue:
  						[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  							[^6]]]
  				ifFalse:
  					[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  						[^7]]].
  		entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint > methodZoneBase ifTrue:
  			["It's a linked send; find which kind."
  			 self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable|
  					 (self asserta: (targetMethod cmType = CMMethod
  								   or: [targetMethod cmType = CMClosedPIC
  								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^8]]]].
  	^0 "keep scanning"!

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 *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	"In Newspeak we support annonymous 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 warnMultiple: cogMethod selectors: aSelectorOop.
  					^nil]]]
  		ifFalse: [self deny: (coInterpreter methodHasCogMethod: aMethodObj)].
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop)
  		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]].
- 	self cppIf: 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]].
  	"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].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	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>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	<var: #originalMethod type: #'CogMethod *'>
  	| methodHeader originalMethod |
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	methodHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: methodHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			methodHeader := originalMethod methodHeader.
+ 			NewspeakVM ifTrue:
- 			self cppIf: NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger.
+ 			 NewspeakVM ifTrue:
- 			self cppIf: NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	processor flushICacheFrom: method asUnsignedInteger to: method asUnsignedInteger + size.
  	^method!

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
+ 	NewspeakVM ifTrue:
+ 		[self generateNewspeakSendTrampolines].
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
- 	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
- 	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
  		[0 to: NumSendTrampolines - 1 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genTrampolineFor: #ceSend:above:to:numArgs:
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
  						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was changed:
  ----- Method: Cogit>>generateTrampolines (in category 'initialization') -----
  generateTrampolines
  	"Generate the run-time entries and exits at the base of the native code zone and update the base.
  	 Read the class-side method trampolines for documentation on the various trampolines"
  	| methodZoneStart |
  	methodZoneStart := methodZoneBase.
  	methodLabel address: methodZoneStart.
  	self allocateOpcodes: 80 bytecodes: 0.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	hasYoungReferent := false.
  	self generateSendTrampolines.
  	self generateMissAbortTrampolines.
  	objectRepresentation generateObjectRepresentationTrampolines.
  	self generateRunTimeTrampolines.
+ 	NewspeakVM ifTrue: [self generateNewspeakRuntime].
+ 	SistaVM ifTrue: [self generateSistaRuntime].
- 	self cppIf: NewspeakVM ifTrue: 	[self generateNewspeakRuntime].
- 	self cppIf: SistaVM ifTrue: [self generateSistaRuntime].
  	self generateEnilopmarts.
  	self generateTracingTrampolines.
  
  	"finish up"
  	self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase.
  	processor flushICacheFrom: methodZoneStart asUnsignedInteger to: methodZoneBase asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>incrementUsageOfTargetIfLinkedSend:mcpc:ignored: (in category 'compaction') -----
  incrementUsageOfTargetIfLinkedSend: annotation mcpc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache |
  			 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "send is linked"
  				[ | targetMethod |
  				entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				self assert: (self isPCWithinMethodZone: targetMethod).
  				targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
  					[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self assert: annotation ~= IsNSSendCall.
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable|
  				 targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
  					[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiterals:pc:method: (in category 'garbage collection') -----
  markLiterals: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.
  	 Additionally in Newspeak, void push implicits that have unmarked classes."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			sel := nsSendCache selector.
  				(objectMemory isForwarded: sel)
  					ifFalse: [objectMemory markAndTrace: sel]
  					ifTrue: [sel := objectMemory followForwarded: literal.
  							nsSendCache selector: sel.
  							self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[(objectRepresentation
  						markAndTraceCacheTagLiteral: cacheTag
  						in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  						atpc: mcpc asUnsignedInteger) ifTrue:
  					["cacheTag is selector" codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache entryPoint targetMethod sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: "Send is linked"
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
  						[self voidNSSendCache: nsSendCache]].
  			sel := nsSendCache selector.
  			(objectMemory isForwarded: sel)
  				ifFalse: [objectMemory markAndTrace: sel]
  				ifTrue: [sel := objectMemory followForwarded: literal.
  						nsSendCache selector: sel.
  						self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable| 
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
  							in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markYoungObjects:pc:method: (in category 'garbage collection') -----
  markYoungObjects: annotation pc: mcpc method: cogMethod
  	"Mark and trace young literals."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
  
+ 	NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
- 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache |
  		 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: nsSendCache selector.
  		 nsSendCache enclosingObject ~= 0 ifTrue:
  			[objectRepresentation markAndTraceLiteralIfYoung: nsSendCache enclosingObject]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: delta
  	<var: #mcpc type: #'char *'>
  	| entryPoint targetMethod unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
  						[self voidNSSendCache: nsSendCache]].
  			^0]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:offset :sendTable|
  				 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
  				 targetMethod cmType ~= CMFree ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (delta - targetMethod objectHeader) negated.
  					 SistaVM ifTrue: "See comment in planCompaction"
  						[methodZone restorePICUsageCount: targetMethod].
  					 ^0].
  				 "Target was freed; map back to an unlinked send; but include this method's reocation"
  				 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  				 unlinkedRoutine := unlinkedRoutine - delta.
  				 backEnd
  					rewriteInlineCacheAt: mcpc asInteger
  					tag: targetMethod selector
  					target: unlinkedRoutine.
  				 ^0]].
  
  	annotation = IsRelativeCall ifTrue:
  		[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  		 ^0].
  
  	annotation = IsAbsPCReference ifTrue:
  		[backEnd relocateMethodReferenceBeforeAddress: mcpc asInteger by: delta].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[literalsManager storeLiteral: mappedLiteral atAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  
+ 	NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
- 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache oop mappedOop |
  		nsSendCache := self nsSendCacheFromReturnAddress: mcpc.
  		oop := nsSendCache selector.	
  		mappedOop := objectRepresentation remapObject: oop.
  		oop ~= mappedOop ifTrue:
  			[nsSendCache selector: mappedOop.
  			(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  		oop := nsSendCache enclosingObject.	
  		oop ~= 0 ifTrue: [
  			mappedOop := objectRepresentation remapObject: oop.
  			oop ~= mappedOop ifTrue:
  				[nsSendCache enclosingObject: mappedOop.
  				(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  		^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
  					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asUnsignedInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			hasYoungPtr ~= 0 ifTrue:
  				["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  				  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  				  the method must remain in youngReferrers if the targetMethod's selector is young."
  				 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :ignored|
  						 (objectMemory isYoung: targetMethod selector) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(targetMethod cmType = CMFree or: [nsSendCache selector = theSelector]) ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 (targetMethod cmType = CMFree
  					  or: [targetMethod selector = theSelector]) ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- 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 |
  
+ 	NewspeakVM ifTrue:
- 	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 changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "Send is linked"
  				[self voidNSSendCache: nsSendCache].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache selector = theSelector ifTrue:
  				[self voidNSSendCache: nsSendCache].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 targetMethod selector = theSelector ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:to: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc to: theCogMethod
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := entryPoint - cmNoCheckEntryOffset.
  				targetMethod = theCogMethod ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 targetMethod asInteger = theCogMethod ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSendToFree:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSendToFree: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #nsTargetMethod type: #'CogMethod *'>
  	| entryPoint |
  
+ 	NewspeakVM ifTrue:
- 	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache nsTargetMethod |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue: "It's a linked send."
  				[nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				nsTargetMethod cmType = CMFree ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable| 
  				 targetMethod cmType = CMFree ifTrue:
  					[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveAllInstances (in category 'object access primitives') -----
  primitiveAllInstances
  	"Answer an array of all instances of the receiver that exist
  	 when the primitive is called, excluding any that may be
  	 garbage collected as a side effect of allocating the result array."
  
  	<export: true>
  	| result |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [(objectMemory isNonImmediate: self stackTop)
+ 			  and: [self objCouldBeClassObj: self stackTop]]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	self cppIf: NewspeakVM
- 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 			[(argumentCount < 1
- 			  or: [(objectMemory isNonImmediate: self stackTop)
- 				  and: [self objCouldBeClassObj: self stackTop]]) ifFalse:
- 				[self primitiveFailFor: PrimErrBadArgument]].
  	result := objectMemory allInstancesOf: self stackTop.
  	(objectMemory isIntegerObject: result) ifTrue:
  		[objectMemory growToAccomodateContainerWithNumSlots: (objectMemory integerValueOf: result).
  		 result := objectMemory allInstancesOf: self stackTop.
  		 (objectMemory isIntegerObject: result) ifTrue:
  			[^self primitiveFailFor: PrimErrNoMemory]].
  	self pop: argumentCount+1 thenPush: result!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBehaviorHash (in category 'object access primitives') -----
  primitiveBehaviorHash
  	| hashOrError |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[argumentCount > 0 ifTrue:
+ 			[((objectMemory isNonImmediate: self stackTop)
+ 			  and: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 				[^self primitiveFailFor: PrimErrBadArgument]]].
- 	self cppIf: NewspeakVM
- 		ifTrue:
- 			[argumentCount > 0 ifTrue:
- 				[((objectMemory isNonImmediate: self stackTop)
- 				  and: [self objCouldBeClassObj: self stackTop]) ifFalse:
- 					[^self primitiveFailFor: PrimErrBadArgument]]].
  	self assert: ((objectMemory isNonImmediate: self stackTop)
  				  and: [self addressCouldBeClassObj: self stackTop]).
  	hashOrError := objectMemory ensureBehaviorHash: self stackTop.
  	hashOrError >= 0
  		ifTrue: [self pop: argumentCount + 1 thenPushInteger: hashOrError]
  		ifFalse: [self primitiveFailFor: hashOrError negated]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNew (in category 'object access primitives') -----
  primitiveNew
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	self cppIf: NewspeakVM
- 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 			[(argumentCount < 1
- 			  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
- 				[self primitiveFailFor: PrimErrBadArgument]].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			["Allocate a new fixed-size instance.  Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
  			(objectMemory instantiateClass: self stackTop)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
  											ifTrue: [PrimErrNoMemory]
  											ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			["Allocate a new fixed-size instance. Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. May cause a GC."
  			| spaceOkay |
  			"The following may cause GC!! Use var for result to permit inlining."
  			spaceOkay := objectMemory
  								sufficientSpaceToInstantiate: self stackTop
  								indexableSize: 0.
  			spaceOkay
  				ifTrue:
  					[self
  						pop: argumentCount + 1
  						thenPush: (objectMemory
  									instantiateClass: self stackTop
  									indexableSize: 0)]
  				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'object access primitives') -----
  primitiveNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
  	| size spaceOkay instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
- 	self cppIf: NewspeakVM
- 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 			[(argumentCount < 2
- 			  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
- 				[self primitiveFailFor: PrimErrBadArgument]].
- 	self successful "positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		ifTrue:
+ 			[(objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
+ 			 spaceOkay
- 			[objectMemory hasSpurMemoryManagerAPI
  				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
- 					[(objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)
- 						ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
- 						ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
- 							  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
- 													and: [(objectMemory isCompiledMethodFormat: instSpec) not])
- 														ifTrue: [PrimErrNoMemory]
- 														ifFalse: [PrimErrBadReceiver])]]
  				ifFalse:
+ 					[self primitiveFailFor: PrimErrNoMemory]]!
- 					[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
- 					 spaceOkay
- 						ifTrue:
- 							[self
- 								pop: argumentCount + 1
- 								thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
- 						ifFalse:
- 							[self primitiveFailFor: PrimErrNoMemory]]]
- 		ifFalse:
- 			[self primitiveFailFor: PrimErrBadArgument]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSizeInBytesOfInstance (in category 'memory space primitives') -----
  primitiveSizeInBytesOfInstance
  	"Answer the byte size of an instance of the receiver.  If num args > 0
  	 then the last argument is a variable size and the size answered is the
  	 size of an instance of the receiver with that many indexable elements."
  	<option: #SpurObjectMemory>
  	| byteSize err |
+ 	NewspeakVM
- 	self cppIf: NewspeakVM
  		ifTrue: "Support VMMirror>>byteSizeOfInstanceOf:WithIndexableVariables:"
  			[argumentCount > 2 ifTrue:
  				[^self primitiveFailFor: PrimErrBadNumArgs]]
  		ifFalse:
  			[argumentCount > 1 ifTrue:
  				[^self primitiveFailFor: PrimErrBadNumArgs]].
  	err := -1.
  	argumentCount >= 1 ifTrue:
  		[(objectMemory isIntegerObject: self stackTop) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument].
  		 byteSize := objectMemory
  						byteSizeOfInstanceOf: (self stackValue: 1)
  						withIndexableSlots: (objectMemory integerValueOf: self stackTop)
  						errInto: [:code| err := code].
  		 err >= 0 ifTrue:
  			[^self primitiveFailFor: err].
  		 ^self pop: argumentCount + 1 thenPush: (self positive64BitIntegerFor: byteSize)].
  	byteSize := objectMemory
  						byteSizeOfInstanceOf: (self stackValue: 0)
  						errInto: [:code| err := code].
  	err >= 0 ifTrue:
  		[^self primitiveFailFor: err].
  	self pop: 1 thenPushInteger: byteSize!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSomeInstance (in category 'object access primitives') -----
  primitiveSomeInstance
  	| class instance |
  	class := self stackTop.
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [(objectMemory isNonImmediate: class)
+ 			  and: [self objCouldBeClassObj: class]]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	self cppIf: NewspeakVM
- 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 			[(argumentCount < 1
- 			  or: [(objectMemory isNonImmediate: class)
- 				  and: [self objCouldBeClassObj: class]]) ifFalse:
- 				[self primitiveFailFor: PrimErrBadArgument]].
  	instance := objectMemory initialInstanceOf: class.
  	instance
  		ifNil: [self primitiveFail]
  		ifNotNil: [self pop: argumentCount+1 thenPush: instance]!

Item was changed:
  ----- Method: StackInterpreter>>flushMethodCache (in category 'method lookup cache') -----
  flushMethodCache
  	"Flush the method cache. The method cache is flushed on every programming change and garbage collect."
  
  	1 to: MethodCacheSize do: [ :i | methodCache at: i put: 0 ].
+ 	NewspeakVM ifTrue:
+ 		[1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0 ]].
- 	self cppIf: NewspeakVM 
- 		ifTrue: [1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0 ]].
  	lastMethodCacheProbeWrite := 0. "this for primitiveExternalMethod"
+ 	self flushAtCache!
- 	self flushAtCache.!

Item was changed:
  ----- Method: StackInterpreter>>flushMethodCacheFrom:to: (in category 'method lookup cache') -----
  flushMethodCacheFrom: memStart to: memEnd 
  	"Flush entries in the method cache only if the oop address is within the given memory range. 
+ 	This reduces over-aggressive cache clearing. Note the AtCache is fully flushed, 70% of the time 
- 	This reduces overagressive cache clearing. Note the AtCache is fully flushed, 70% of the time 
  	cache entries live in newspace, new objects die young"
  	| probe |
  	probe := 0.
+ 	1 to: MethodCacheEntries do:
+ 		[:i | 
+ 		(methodCache at: probe + MethodCacheSelector) = 0 ifFalse:
+ 			[((((self oop: (methodCache at: probe + MethodCacheSelector) isGreaterThanOrEqualTo: memStart)
+ 				 and: [self oop: (methodCache at: probe + MethodCacheSelector) isLessThan: memEnd])
+ 			 or: [(self oop: (methodCache at: probe + MethodCacheClass) isGreaterThanOrEqualTo: memStart)
+ 				 and: [self oop: (methodCache at: probe + MethodCacheClass) isLessThan: memEnd]])
+ 			 or: [(self oop: (methodCache at: probe + MethodCacheMethod) isGreaterThanOrEqualTo: memStart)
+ 				 and: [self oop: (methodCache at: probe + MethodCacheMethod) isLessThan: memEnd]]) ifTrue:
+ 				[methodCache at: probe + MethodCacheSelector put: 0]].
- 	1 to: MethodCacheEntries do: [:i | 
- 			(methodCache at: probe + MethodCacheSelector) = 0
- 				ifFalse: [((((self oop: (methodCache at: probe + MethodCacheSelector) isGreaterThanOrEqualTo: memStart)
- 										and: [self oop: (methodCache at: probe + MethodCacheSelector) isLessThan: memEnd])
- 									or: [(self oop: (methodCache at: probe + MethodCacheClass) isGreaterThanOrEqualTo: memStart)
- 											and: [self oop: (methodCache at: probe + MethodCacheClass) isLessThan: memEnd]])
- 								or: [(self oop: (methodCache at: probe + MethodCacheMethod) isGreaterThanOrEqualTo: memStart)
- 										and: [self oop: (methodCache at: probe + MethodCacheMethod) isLessThan: memEnd]])
- 						ifTrue: [methodCache at: probe + MethodCacheSelector put: 0]].
  			probe := probe + MethodCacheEntrySize].
+ 	NewspeakVM ifTrue:
+ 		[1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0]].
- 	self cppIf: NewspeakVM 
- 		ifTrue: [1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0 ]].
  	self flushAtCache!

Item was changed:
  ----- Method: StackInterpreter>>internalFindNewMethodOrdinary (in category 'message sending') -----
  internalFindNewMethodOrdinary
  	"Find the compiled method to be run when the current messageSelector is sent to the class 'lkupClass', setting the values of 'newMethod' and 'primitiveIndex'."
  	<inline: true>
  	(self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifFalse:
  		["entry was not found in the cache; look it up the hard way"
  		 self externalizeIPandSP.
  		 ((objectMemory isOopForwarded: messageSelector)
  		  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
  			[(objectMemory isOopForwarded: messageSelector) ifTrue:
  				[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  			 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
  				[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
  			(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
  				[^nil]].
  		 lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 		 NewspeakVM
- 		 self cppIf: #NewspeakVM
  			ifTrue: [self lookupOrdinarySend]
  			ifFalse: [self lookupMethodInClass: lkupClass].
  		 self internalizeIPandSP.
  		 self addNewMethodToCache: lkupClass].
  !

Item was changed:
  ----- Method: StackInterpreter>>methodClassOf: (in category 'compiled methods') -----
  methodClassOf: methodPointer
  	<api>
  	"Using a read barrier here simplifies the become implementation and costs very little
  	 because the class index and ValueIndex of the association almost certainly share a cache line."
+ 	| literal |
+ 	literal := self followLiteral: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
+ 	^NewspeakVM
- 	^self cppIf: NewspeakVM
  		ifTrue:
+ 			[literal = objectMemory nilObject
- 			[| literal |
- 			 literal := self followLiteral: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
- 			 literal = objectMemory nilObject
  				ifTrue: [literal]
  				ifFalse: [objectMemory followField: ValueIndex ofObject: literal]]
  		ifFalse:
+ 			[self assert: ((objectMemory isPointers: literal) and: [(objectMemory numSlotsOf: literal) > ValueIndex]).
- 			[| literal |
- 			 literal := self followLiteral: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
- 			 self assert: ((objectMemory isPointers: literal) and: [(objectMemory numSlotsOf: literal) > ValueIndex]).
  			 objectMemory followField: ValueIndex ofObject: literal]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
+ 	NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
- 	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
- 	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
  		[0 to: NumSendTrampolines - 1 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
  						  numArgs: numArgs
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
  						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!



More information about the Vm-dev mailing list