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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 31 16:13:42 UTC 2015


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

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

Name: VMMaker.oscog-eem.1134
Author: eem
Time: 31 March 2015, 9:11:36.572 am
UUID: 5ce56810-9b43-406a-8935-c292cd5cfed8
Ancestors: VMMaker.oscog-tfel.1133

Integrate Ryan's new self-send scheme which
eliminates the clumsy and slow implicit receiver
cache.

Minor edits to not generate an include of
nsmethodcache.h in non-Newspeak VMs.

Soon we should nuke the NewspeakV3 bytecode
set initializers and eliminate NSSendIsPCAnnotated.

=============== Diff against VMMaker.oscog-tfel.1133 ===============

Item was changed:
  ----- Method: CoInterpreter class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	"Answer any extra classes to be included in the translation."
  	^((super ancilliaryClasses: options) copyWithout: InterpreterStackPages),
  	   {	CoInterpreterStackPages.
+ 		CogBlockMethod. NSSendCache },
- 		CogBlockMethod },
  	((Cogit ancilliaryClasses: options) select: [:class| class inheritsFrom: CogBlockMethod])!

Item was changed:
  ----- Method: CoInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Override to avoid repeating StackInterpreter's declarations and add our own extensions"
  	| threaded |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	threaded := aCCodeGenerator vmClass isThreadedVM.
  	aCCodeGenerator
  		addHeaderFile:'"sqCogStackAlignment.h"';
+ 		addHeaderFile:'"cogmethod.h"'.
+ 	NewspeakVM ifTrue:
+ 		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
+ 	aCCodeGenerator
- 		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile: (threaded ifTrue: ['"cointerpmt.h"'] ifFalse: ['"cointerp.h"']);
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator vmClass
  		declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: (threaded ifTrue: ['Cog MT'] ifFalse: ['Cog']).
  	aCCodeGenerator
  		var: #heapBase type: #usqInt;
  		var: #statCodeCompactionUsecs type: #usqLong;
  		var: #maxLiteralCountForCompile
  			declareC: 'sqInt maxLiteralCountForCompile = MaxLiteralCountForCompile /* ', MaxLiteralCountForCompile printString, ' */';
  		var: #minBackwardJumpCountForCompile
  			declareC: 'sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* ', MinBackwardJumpCountForCompile printString, ' */'.
  	aCCodeGenerator
  		var: #reenterInterpreter
  		declareC: 'jmp_buf reenterInterpreter; /* private export */'.
  	aCCodeGenerator
  		var: #primTraceLogIndex type: #'unsigned char';
  		var: #primTraceLog declareC: 'sqInt primTraceLog[256]';
  		var: #traceLog
  		declareC: 'sqInt traceLog[TraceBufferSize /* ', TraceBufferSize printString, ' */]';
  		var: #traceSources type: #'char *' array: TraceSources!

Item was added:
+ ----- Method: CoInterpreter>>ceImplicitReceiverSend:receiver: (in category 'trampolines') -----
+ ceImplicitReceiverSend: cacheAddress receiver: methodReceiver
+ 	"An implicit receiver send cache missed."
+ 	| nsSendCache methodMixin numArgs selector implicitReceiver cogMethod irClassTag mrClassTag errSelIdx |
+ 	<api>
+ 	<option: #NewspeakVM>
+ 	<inline: false>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 
+ 	cogit assertCStackWellAligned.
+ 	self assert: (objectMemory addressCouldBeOop: methodReceiver).
+ 
+ 	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
+ 	selector := nsSendCache selector.
+ 	numArgs := nsSendCache numArgs.
+ 	methodMixin := self mMethodClass.
+ 
+ 	implicitReceiver := self
+ 		implicitReceiverFor: methodReceiver
+ 		mixin: methodMixin
+ 		implementing: selector.
+ 
+ 	self assert: (self stackValue: numArgs + 1 "ret val") = methodReceiver.
+ 	self stackValue: numArgs + 1 "ret val " put: implicitReceiver.
+ 	"Replace the methodReceiver on the stack with the implicitReceiver. When the cache has
+ 	a hit, we don't care that the value on the stack is wrong because the compiled callee will
+ 	use the value in ReceiverResultReg to build its frame. But the interpreter will use
+ 	stack(numArgs)."
+ 
+ 	mrClassTag := objectMemory fetchClassTagOf: methodReceiver.
+ 	irClassTag := objectMemory fetchClassTagOf: implicitReceiver.
+ 	argumentCount := numArgs.
+ 
+ 	(self lookupInMethodCacheSel: selector classTag: irClassTag)
+ 		ifTrue: ["check for coggability because method is in the cache"
+ 			self ifAppropriateCompileToNativeCode: newMethod selector: selector]
+ 		ifFalse: [
+ 			(objectMemory isOopForwarded: selector) ifTrue:
+ 				[self error: 'Selector should have fixed by mapObjectReferencesInMachineCodeForBecome'].
+ 			(objectMemory isForwardedClassTag: irClassTag) ifTrue:
+ 				[self error: 'Implicit receiver lookup should have followed fowarded objects'].
+ 			messageSelector := selector.
+ 			(errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: irClassTag)) ~= 0
+ 				ifTrue: [[self handleMNU: errSelIdx InMachineCodeTo: implicitReceiver classForMessage: (objectMemory classForClassTag: irClassTag).
+ 						self error: 'UNREACHABLE3']]].
+ 
+ 	(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
+ 						linkNSSendCache: nsSendCache 
+ 						classTag: mrClassTag
+ 						enclosingObject: (implicitReceiver = methodReceiver
+ 							ifTrue: [0] ifFalse: [implicitReceiver])
+ 						target: cogMethod
+ 						caller: self mframeHomeMethodExport]
+ 				ifFalse: [self error: 'What does this mean? C.f. case in ceSend:...'].
+ 			instructionPointer := self popStack.
+ 			self executeNewMethod.
+ 			self error: 'UNREACHABLE 1'].
+ 	instructionPointer := self popStack.
+ 	self interpretMethodFromMachineCode.
+ 	self error: 'UNREACHABLE 2'.
+ 	^nil!

Item was changed:
  ----- Method: CogIA32Compiler>>implicitReceiveCacheAt: (in category 'inline cacheing') -----
  implicitReceiveCacheAt: callSiteReturnAddress
  	"Answer the implicit receiver cache for the return address
  	 of a call to the ceImplicitReceiverTrampoline."
  	<option: #NewspeakVM>
  	<var: #callSiteReturnAddress type: #'char *'>
  	<inline: false>
+ 	^self literalBeforeFollowingAddress: callSiteReturnAddress asUnsignedInteger - 5 "sizeofcall"!
- 	^self literalBeforeFollowingAddress: callSiteReturnAddress asUnsignedInteger - 10!

Item was changed:
  ----- Method: CogVMSimulator>>cCoerceSimple:to: (in category 'translation support') -----
  cCoerceSimple: value to: cTypeString
  	"Type coercion for translation and simulation.
  	 For simulation answer a suitable surrogate for the struct types"
  	^cTypeString caseOf:
  	   {	[#'char *']				->	[value].
  		[#'void *']				->	[value].
  		[#sqInt]					->	[value].
  		[#'void (*)()']			->	[value].
  		[#'void (*)(void)']		->	[value].
  		[#'CogMethod *']		->	[cogit cogMethodSurrogateAt: value asUnsignedInteger].
+ 		[#'CogBlockMethod *']	->	[cogit cogBlockMethodSurrogateAt: value asUnsignedInteger].
+ 		[#'NSSendCache *']		->	[cogit nsSendCacheSurrogateAt: value asUnsignedInteger]. }!
- 		[#'CogBlockMethod *']	->	[cogit cogBlockMethodSurrogateAt: value asUnsignedInteger] }!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset selfSendEntry selfSendEntryAlignment cmSelfSendEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines dynamicSuperSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines nsSendCacheSurrogateClass'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSendTrampolines NumTrampolines ProcessorClass'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs selfSendEntry cmSelfSendEntryOffset selfSendEntryAlignment selfSendTrampolines'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerIRC NumSendTrampolines NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>additionalHeadersDo: (in category 'translation') -----
  additionalHeadersDo: aBinaryBlock
  	"Evaluate aBinaryBlock with the names and contents of
  	 any additional header files that need to be generated."
+ 
+ 	NewspeakVM ifTrue:
+ 		[aBinaryBlock
+ 			value: 'cogmethod.h'
+ 			value: NewspeakCogMethod cogMethodHeader.
+ 		 aBinaryBlock
+ 			value: 'nssendcache.h'
+ 			value: NSSendCache typedef.
+ 		 ^self].
+ 
  	aBinaryBlock
  		value: 'cogmethod.h'
+ 		value: CogMethod cogMethodHeader!
- 		value: (NewspeakVM
- 					ifTrue: [NewspeakCogMethod]
- 					ifFalse: [CogMethod]) cogMethodHeader!

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
  	^{	CogMethodZone.
  		CogAbstractInstruction.
  		ProcessorClass basicNew abstractInstructionCompilerClass.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogInstructionAnnotation.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
  		CogMethod },
  	((options at: #NewspeakVM ifAbsent: [false])
+ 		ifTrue: [{NewspeakCogMethod. NSSendCache}]
- 		ifTrue: [{NewspeakCogMethod}]
  		ifFalse: [#()])!

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
+ 		[#(	'selfSendEntry' 'selfSendEntryAlignment' 'cmSelfSendEntryOffset'
+ 			'dynSuperEntry' 'dynSuperEntryAlignment' 'cmDynSuperEntryOffset'
+ 			'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'implicitReceiverSendTrampolines'
+ 			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
- 		[#(	'selfSendEntry' 'selfSendEntryAlignment' 'dynSuperEntry' 'dynSuperEntryAlignment'
- 			'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'ceImplicitReceiverTrampoline'
- 			'ceEnclosingObjectTrampoline' 'cmSelfSendEntryOffset' 'cmDynSuperEntryOffset'
- 			'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must preceed cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
+ 		addHeaderFile:'"cogmethod.h"'.
+ 	NewspeakVM ifTrue:
+ 		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
+ 	aCCodeGenerator
- 		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *, void *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel';
  		var: #primInvokeLabel type: #'AbstractInstruction *'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
+ 					stackOverflowCall sendMiss
+ 					entry noCheckEntry selfSendEntry dynSuperEntry
- 					stackOverflowCall sendMiss entry noCheckEntry selfSendEntry dynSuperEntry
  					picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #annotations type: #'InstructionAnnotation *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #selfSendTrampolines
  			declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
+ 		var: #implicitReceiverSendTrampolines
+ 			declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator);
  			var: #primitiveGeneratorTable
  				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration isNil ifTrue:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (initializationOptions at: #ISA ifAbsent: [#IA32]) caseOf: {
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien]. }.
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
+ 
+ 	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
+ 	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
+ 	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
+ 	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
+ 	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
+ 	NumOopsPerNSC := NSSendCache instVarNames size.
+ 
- 	"The implicit receiver cache has two entries, class and mixin oops."
- 	NumOopsPerIRC := 2.
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was changed:
  ----- Method: Cogit class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM
  	 support code.  include cePositive32BitIntegerTrampoline as a hack to prevent it being inlined (it is
  	 only used outside of Cogit by the object representation).  Include CFramePointer CStackPointer as
  	 a hack to get them declared at all."
  	^#('ceBaseFrameReturnTrampoline' 'ceCaptureCStackPointers' 'ceCheckForInterruptTrampoline'
  		'ceEnterCogCodePopReceiverReg' 'realCEEnterCogCodePopReceiverReg'
  		'ceCallCogCodePopReceiverReg' 'realCECallCogCodePopReceiverReg'
  		'ceCallCogCodePopReceiverAndClassRegs' 'realCECallCogCodePopReceiverAndClassRegs'
  		'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
  		'ceTryLockVMOwner' 'ceUnlockVMOwner'
+ 		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'cmSelfSendEntryOffset' 'missOffset'
- 		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'missOffset'
  		'blockNoContextSwitchOffset' 'breakPC'
  		'CFramePointer' 'CStackPointer' 'cFramePointerInUse' 'ceGetSP'
  		'traceFlags' 'traceStores' 'debugPrimCallStackOffset')
  			includes: var!

Item was changed:
  ----- Method: Cogit class>>shouldGenerateTypedefFor: (in category 'translation') -----
  shouldGenerateTypedefFor: aStructClass
  	"Hack to work-around mutliple definitions.  Sometimes a type has been defined in an include."
+ 	^({ CogBlockMethod. CogMethod. SistaCogMethod. NewspeakCogMethod. NSSendCache } includes: aStructClass) not!
- 	^({ CogBlockMethod. CogMethod. SistaCogMethod. NewspeakCogMethod } includes: aStructClass) not!

Item was changed:
  ----- Method: Cogit>>cCoerceSimple:to: (in category 'translation support') -----
  cCoerceSimple: value to: cTypeString
  	<doNotGenerate>
  	cTypeString == #'CogMethod *' ifTrue:
  		[^(value isInteger and: [value < 0])
  			ifTrue: [value] "it's an error code; leave it be"
  			ifFalse: [self cogMethodSurrogateAt: value asUnsignedInteger]].
  	cTypeString == #'CogBlockMethod *' ifTrue:
  		[^self cogBlockMethodSurrogateAt: value asUnsignedInteger].
+ 	cTypeString == #'NSSendCache *' ifTrue:
+ 		[^self nsSendCacheSurrogateAt: value asUnsignedInteger].
  	(cTypeString == #'AbstractInstruction *'
  	 and: [value isBehavior]) ifTrue:
  		[^processor abstractInstructionCompilerClass].
  	^super cCoerceSimple: value to: cTypeString!

Item was removed:
- ----- Method: Cogit>>ceImplicitReceiverFor:receiver: (in category 'in-line cacheing') -----
- ceImplicitReceiverFor: selector receiver: receiver
- 	"Cached implicit receiver implementation.  Caller looks like
- 		mov selector, ClassReg
- 				call ceImplicitReceiver
- 				br continue
- 		Lclass	.word
- 		Lmixin:	.word
- 		continue:
- 	 The trampoline has already fetched the class and probed the cache and found
- 	 that the cache missed.  Compute the implicit receiver for the receiver's class
- 	 and reload the class tag.  If either the class tag or the mixin are young then the
- 	 method needs to be added to the youngReferrers list to ensure correct GC."
- 
- 	<option: #SqueakV3ObjectMemory>
- 	| rcvrClass retpc classpc mixinpc mixin cogMethod |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	retpc := coInterpreter stackTop.
- 	classpc := retpc + backEnd jumpShortByteSize.
- 	mixinpc := retpc + backEnd jumpShortByteSize + objectMemory bytesPerOop.
- 	mixin := coInterpreter
- 				implicitReceiverFor: receiver
- 				mixin: coInterpreter mMethodClass
- 				implementing: selector.
- 	rcvrClass := objectMemory fetchClassOf: receiver.
- 	cogMethod := coInterpreter mframeHomeMethodExport.
- 	cogMethod cmRefersToYoung ifFalse:
- 		[((objectRepresentation inlineCacheTagsMayBeObjects
- 		   and: [objectMemory isYoung: rcvrClass])
- 		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
- 			[methodZone ensureInYoungReferrers: cogMethod]].
- 	backEnd
- 		unalignedLongAt: classpc
- 			put: (objectRepresentation inlineCacheTagForClass: rcvrClass);
- 		unalignedLongAt: mixinpc
- 			put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
- 	^mixin!

Item was removed:
- ----- Method: Cogit>>ceImplicitReceiverFor:receiver:cache: (in category 'in-line cacheing') -----
- ceImplicitReceiverFor: selector receiver: receiver cache: cacheAddress
- 	"Cached implicit receiver implementation.  Caller looks like
- 				mov Lclass, Arg1Reg
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 	 and Lclass: .word; Lmixin: .word is somewhere on the heap.
- 	 The trampoline has already fetched the class and probed the cache and found
- 	 that the cache missed.  Compute the implicit receiver for the receiver's class
- 	 and reload the class tag.  If either the class tag or the mixin are young then the
- 	 method needs to be added to the youngReferrers list to ensure correct GC."
- 
- 	<option: #SpurObjectMemory>
- 	<var: #cacheAddress type: #usqInt>
- 	| rcvrClass mixin cogMethod |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	mixin := coInterpreter
- 				implicitReceiverFor: receiver
- 				mixin: coInterpreter mMethodClass
- 				implementing: selector.
- 	rcvrClass := objectMemory fetchClassOf: receiver.
- 	cogMethod := coInterpreter mframeHomeMethodExport.
- 	cogMethod cmRefersToYoung ifFalse:
- 		[((objectRepresentation inlineCacheTagsMayBeObjects
- 		   and: [objectMemory isYoung: rcvrClass])
- 		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
- 			[methodZone ensureInYoungReferrers: cogMethod]].
- 	backEnd
- 		unalignedLongAt: cacheAddress
- 			put: (objectRepresentation inlineCacheTagForClass: rcvrClass);
- 		unalignedLongAt: cacheAddress + objectMemory bytesPerOop
- 			put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
- 	^mixin!

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
+ 	| nsSendCache |
  	<var: #mcpc type: #'char *'>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[ | 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]]]]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: 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
  	<var: #mcpc type: #'char *'>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	| literal entryPoint nsSendCache |
- 	| literal entryPoint |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (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]]].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[ | 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]]]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: 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 into:
  					[:targetMethod :sendTable|
  					 (self asserta: (targetMethod cmType = CMMethod
  								   or: [targetMethod cmType = CMClosedPIC
  								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^8]]]].
  	^0 "keep scanning"!

Item was added:
+ ----- 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 *'>
+ 	opcodeIndex := 0.
+ 	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.
+ 	"We don't patch stack(-numArgs). See comment in ceImplicitReceiverSend:receiver:"
+ 	jumpItsTheReceiverStupid jmpTarget: self Label.
+ 	self MoveMw: NSCTargetIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
+ 	self JumpR: TempReg.
+ 
+ 	jumpMiss jmpTarget: self Label.
+ 	objectRepresentation
+ 		genEnsureObjInRegNotForwarded: ReceiverResultReg
+ 		scratchReg: TempReg
+ 		updatingMw: FoxMFReceiver
+ 		r: FPReg.
+ 	backEnd genPushRegisterArgsForNumArgs: numArgs.
+ 	^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 changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
+ 	"Generate the non-send runtime support for Newspeak: push enclosing object.
+ 	The dynamic frequency is so low we merely call an interpreter routine."
- 	| jumpMiss jumpItsTheReceiverStupid retpcReg |
- 	<var: #jumpMiss type: #'AbstractInstruction *'>
- 	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
- 	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
- 	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
  	ceEnclosingObjectTrampoline := self genTrampolineFor: #ceEnclosingObjectAt:
  										called: 'ceEnclosingObjectTrampoline'
  										arg: SendNumArgsReg
+ 										result: ReceiverResultReg.!
- 										result: ReceiverResultReg.
- 	"Cached push implicit receiver implementation.  If objectRepresentation doesn't support
- 	 pinning then caller looks like
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 				br continue
- 		Lclass:	.word
- 		Lmixin::	.word
- 		continue:
- 	 If objectRepresentation supports pinning then caller looks like
- 				mov Lclass, Arg1Reg
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 	 and Lclass: .word; Lmixin: .word is somewhere on the heap.
- 
- 	 If class tag matches class of receiver then mixin contains either 0 or the implicit receiver.
- 	 If 0, answer the actual receiver, otherwise the mixin.
- 	 Generate the class fetch and cache probe inline for speed.
- 	 Smashes Arg1Reg, RegClass and caller-saved regs."
- 	opcodeIndex := 0.
- 	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
- 	objectRepresentation
- 		genGetInlineCacheClassTagFrom: ReceiverResultReg
- 		into: ClassReg
- 		forEntry: false.
- 	objectRepresentation canPinObjects
- 		ifTrue:
- 			[self MoveMw: 0 r: Arg1Reg R: TempReg.
- 			 self CmpR: ClassReg R: TempReg.
- 			 jumpMiss := self JumpNonZero: 0.
- 			 self MoveMw: objectMemory bytesPerOop r: Arg1Reg R: TempReg.
- 			 self CmpCq: 0 R: TempReg.
- 			 jumpItsTheReceiverStupid := self JumpZero: 0.
- 			 self MoveR: TempReg R: ReceiverResultReg.
- 			 jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
- 			 jumpMiss jmpTarget: self Label.
- 			 objectRepresentation
- 				genEnsureObjInRegNotForwarded: ReceiverResultReg
- 				scratchReg: TempReg
- 				updatingMw: FoxMFReceiver
- 				r: FPReg.
- 			 ceImplicitReceiverTrampoline := self
- 												genTrampolineFor: #ceImplicitReceiverFor:receiver:cache:
- 												called: 'ceImplicitReceiverTrampoline'
- 												numArgs: 3
- 												arg: SendNumArgsReg
- 												arg: ReceiverResultReg
- 												arg: Arg1Reg
- 												arg: nil
- 												saveRegs: false
- 												pushLinkReg: true
- 												resultReg: ReceiverResultReg
- 												appendOpcodes: true]
- 		ifFalse:
- 			[backEnd hasLinkRegister
- 				ifTrue: [retpcReg := LinkReg]
- 				ifFalse: [self MoveMw: 0 r: SPReg R: (retpcReg := TempReg)].
- 			 self MoveMw: 0 r: SPReg R: retpcReg.
- 			 self MoveMw: backEnd jumpShortByteSize r: retpcReg R: Arg1Reg.
- 			 self CmpR: ClassReg R: Arg1Reg.
- 			 jumpMiss := self JumpNonZero: 0.
- 			 self MoveMw: backEnd jumpShortByteSize + objectMemory bytesPerOop r: retpcReg R: ClassReg.
- 			 self CmpCq: 0 R: ClassReg.
- 			 jumpItsTheReceiverStupid := self JumpZero: 0.
- 			 self MoveR: ClassReg R: ReceiverResultReg.
- 			 jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
- 			 jumpMiss jmpTarget: self Label.
- 			 ceImplicitReceiverTrampoline := self
- 												genTrampolineFor: #ceImplicitReceiverFor:receiver:
- 												called: 'ceImplicitReceiverTrampoline'
- 												numArgs: 2
- 												arg: SendNumArgsReg
- 												arg: ReceiverResultReg
- 												arg: nil
- 												arg: nil
- 												saveRegs: false
- 												pushLinkReg: true
- 												resultReg: ReceiverResultReg
- 												appendOpcodes: true]!

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

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 2 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: numArgs)].
  	ordinarySendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					called: (self trampolineName: 'ceSend' numArgs: -1)
  					arg: ClassReg
  					arg: 0
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
+ 
+ 	"Generate these in the middle so they are within [firstSend, lastSend]."
+ 	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
+ 
- 	self cppIf: NewspeakVM
- 		ifTrue:
- 			[0 to: NumSendTrampolines - 2 do:
- 				[:numArgs|
- 				dynamicSuperSendTrampolines
- 					at: numArgs
- 					put: (self genTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 							  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
- 							  arg: ClassReg
- 							  arg: ReceiverResultReg
- 							  arg: numArgs)].
- 			dynamicSuperSendTrampolines
- 				at: NumSendTrampolines - 1
- 				put: (self genTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 							called: (self trampolineName: 'ceDynSuperSend' numArgs: -1)
- 							arg: ClassReg
- 							arg: ReceiverResultReg
- 							arg: SendNumArgsReg).
- 			0 to: NumSendTrampolines - 2 do:
- 				[:numArgs|
- 				selfSendTrampolines
- 					at: numArgs
- 					put: (self genTrampolineFor: #ceSelfSend:to:numArgs:
- 							  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
- 							  arg: ClassReg
- 							  arg: ReceiverResultReg
- 							  arg: numArgs)].
- 			selfSendTrampolines
- 				at: NumSendTrampolines - 1
- 				put: (self genTrampolineFor: #ceSelfSend:to:numArgs:
- 							called: (self trampolineName: 'ceSelfSend' numArgs: -1)
- 							arg: ClassReg
- 							arg: ReceiverResultReg
- 							arg: SendNumArgsReg)].
  	0 to: NumSendTrampolines - 2 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: numArgs)].
  	superSendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
  					arg: ClassReg
  					arg: 1
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was changed:
  ----- Method: Cogit>>implicitReceiverCacheAddressAt: (in category 'newspeak support') -----
  implicitReceiverCacheAddressAt: mcpc
+ 	"Caller looks like
+ 		mov LcacheAddress, SendNumArgsReg
+ 		call ceImplicitReceiver"
- 	"Cached push implicit receiver implementation.  If objectRepresentation doesn't support
- 	 pinning then caller looks like
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 				br continue
- 		Lclass:	.word
- 		Lmixin::	.word
- 		continue:
- 	 If objectRepresentation supports pinning then caller looks like
- 				mov Lclass, Arg1Reg
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 	 and Lclass: .word; Lmixin: .word is somewhere on the heap."
  	<option: #NewspeakVM>
  	<var: #mcpc type: #'char *'>
  	<inline: true>
+ 	self assert: false.
+ 	^self cCoerceSimple: (backEnd implicitReceiveCacheAt: mcpc) asUnsignedInteger to: #'NSSendCache *'
+ !
- 	<returnTypeC: #usqInt>
- 	^objectRepresentation canPinObjects
- 		ifTrue:
- 			[(backEnd implicitReceiveCacheAt: mcpc) asUnsignedInteger]
- 		ifFalse:
- 			[mcpc asUnsignedInteger + backEnd jumpShortByteSize]!

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 nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		nsSendCache classTag ~= 0 ifTrue: "send is linked"
+ 			[ | targetMethod |
+ 			entryPoint := nsSendCache target.
+ 			targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 			self assert: (self isPCWithinMethodZone: targetMethod asUnsignedInteger).
+ 			targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
+ 				[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
+ 
+ 	annotation = IsSendCall ifTrue:
+ 		[self assert: annotation ~= IsNSSendCall.
+ 		entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
- 		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint into:
  				[:targetMethod :sendTable|
  				 targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
  					[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
+ 
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>initialize (in category 'initialization') -----
  initialize
  	| wordSize |
  	wordSize := self class objectMemoryClass wordSize.
  	cogMethodSurrogateClass := NewspeakVM
  									ifTrue:
  										[wordSize = 4
  											ifTrue: [NewspeakCogMethodSurrogate32]
  											ifFalse: [NewspeakCogMethodSurrogate64]]
  									ifFalse:
  										[wordSize = 4
  											ifTrue: [CogMethodSurrogate32]
  											ifFalse: [CogMethodSurrogate64]].
  	cogBlockMethodSurrogateClass := wordSize = 4
  											ifTrue: [CogBlockMethodSurrogate32]
+ 											ifFalse: [CogBlockMethodSurrogate64].
+ 	nsSendCacheSurrogateClass := wordSize = 4
+ 											ifTrue: [NSSendCacheSurrogate32]
+ 											ifFalse: [NSSendCacheSurrogate64].!
- 											ifFalse: [CogBlockMethodSurrogate64]!

Item was added:
+ ----- Method: Cogit>>initializeNSSendCache:selector:numArgs: (in category 'newspeak support') -----
+ initializeNSSendCache: cacheAddress selector: selector numArgs: numArgs
+ 	| nsSendCache |
+ 	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
+ 	nsSendCache selector: selector.
+ 	nsSendCache numArgs: numArgs.
+ 	nsSendCache classTag: 0. "Illegal class tag"!

Item was changed:
  ----- Method: Cogit>>isPCMappedAnnotation:alternateInstructionSet: (in category 'method map') -----
  isPCMappedAnnotation: annotation alternateInstructionSet: isAlternateInstSet
  	<inline: true>
  	^self cppIf: NewspeakVM
  		ifTrue:
- 			"For Newspeak we shoe-horn in implicit receiver inline cache handling as an inline
- 			 send, since these caches are processed similarly to inline send caches.  But if
- 			 the Newspeak instruction set includes an absent receiver send then there are
- 			 two map entries for the one bytecode, the first for the implicit receiver cache
- 			 and the second for the send cache. Only one of these can function as the pc-
- 			 mapped entry since there is only one bytecode. c.f. isSendAnnotation:"
  			[annotation = IsSendCall
+ 			or: [annotation = IsNSSendCall
- 			or: [(annotation = IsNSSendCall
- 				and: [isAlternateInstSet
- 						ifTrue: [AltNSSendIsPCAnnotated]
- 						ifFalse: [NSSendIsPCAnnotated]])
  			or: [annotation = HasBytecodePC]]]
  		ifFalse:
+ 			[(annotation = IsSendCall)
- 			[(self isSendAnnotation: annotation)
  			  or: [annotation = HasBytecodePC]]!

Item was added:
+ ----- Method: Cogit>>linkNSSendCache:classTag:enclosingObject:target:caller: (in category 'newspeak support') -----
+ linkNSSendCache: nsSendCache classTag: classTag enclosingObject: enclosingObject target: targetMethod caller: callingMethod
+ 	<api>
+ 	<option: #NewspeakVM>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	<var: #targetMethod type: #'CogMethod *'>
+ 	<var: #callingMethod type: #'CogMethod *'>
+ 	nsSendCache classTag: classTag.
+ 	nsSendCache enclosingObject: enclosingObject.
+ 	nsSendCache target: targetMethod asInteger + cmNoCheckEntryOffset.
+ 	callingMethod cmRefersToYoung ifFalse:
+ 		[(enclosingObject ~= 0 and: [objectMemory isYoung: enclosingObject]) ifTrue:
+ 			[methodZone ensureInYoungReferrers: callingMethod]].
+ !

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 nsSendCache |
- 	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[ | 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 *')]]]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: 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]]]].
+ 
- 					[codeModified := true]].  "cacheTag is selector"
- 			  self cppIf: NewspeakVM ifTrue:
- 				[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 					[| cacheAddress class mixin |
- 					 self assert: NumOopsPerIRC = 2.
- 					 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 					 (class := backEnd unalignedLongAt: cacheAddress) ~= 0
- 						ifTrue:
- 							[(objectRepresentation cacheTagIsMarked: class)
- 								ifTrue:
- 									[(mixin := backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop) ~= 0 ifTrue:
- 										[objectRepresentation
- 											markAndTraceLiteral: mixin
- 											in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
- 											at: (self asAddress: (cacheAddress + objectMemory bytesPerOop) asVoidPointer
- 													put: [:val| backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: val])]]
- 								ifFalse:
- 									[backEnd
- 										unalignedLongAt: cacheAddress put: 0;
- 										unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: 0.
- 									 codeModified := true]]
- 						ifFalse:
- 							[self assert: (backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop) = 0]]]]].
  	^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 nsSendCache |
- 	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[ | entryPoint targetMethod sel eo |
+ 		nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		entryPoint := nsSendCache target.
+ 		entryPoint ~= 0 ifTrue: "Send is linked"
+ 			[targetMethod := entryPoint - cmNoCheckEntryOffset.
+ 			(self markAndTraceOrFreeCogMethod: targetMethod
+ 				firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
+ 					[nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
+ 		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 *')]]]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
+ 			self assert: annotation ~= IsNSSendCall.
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint 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: cogMethod
  							atpc: mcpc asUnsignedInteger) ifTrue:
+ 						[codeModified := true]]]].
+ 
- 						[codeModified := true].
- 					 self cppIf: NewspeakVM ifTrue:
- 						[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 							[| cacheAddress class mixin |
- 							 (objectRepresentation
- 									markAndTraceCacheTagLiteral: cacheTag
- 									in: cogMethod
- 									atpc: mcpc asUnsignedInteger) ifTrue:
- 								[codeModified := true].  "cacheTag is selector"
- 							 self assert: NumOopsPerIRC = 2.
- 							 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 							 (class := backEnd unalignedLongAt: cacheAddress) ~= 0
- 								ifTrue:
- 									[(objectRepresentation cacheTagIsMarked: class)
- 										ifTrue:
- 											[(mixin := backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop) ~= 0 ifTrue:
- 												[objectRepresentation
- 													markAndTraceLiteral: mixin
- 													in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
- 													at: (self asAddress: cacheAddress + objectMemory bytesPerOop
- 															put: [:val| backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: val])]]
- 										ifFalse:
- 											[backEnd
- 												unalignedLongAt: cacheAddress put: 0;
- 												unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: 0.
- 											 codeModified := true]]
- 								ifFalse:
- 									[self assert: (backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop) = 0]]]]]].
  	^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 nsSendCache |
- 	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		objectRepresentation markAndTraceLiteralIfYoung: nsSendCache selector.
+ 		nsSendCache enclosingObject ~= 0 ifTrue:
+ 			[objectRepresentation markAndTraceLiteralIfYoung: nsSendCache enclosingObject]]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
+ 				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag]]].
+ 
- 				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag].
- 				 self cppIf: NewspeakVM ifTrue:
- 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 						[| cacheAddress class mixin |
- 						 self assert: NumOopsPerIRC = 2.
- 						 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 						 class := backEnd unalignedLongAt: cacheAddress.
- 						 class ~= 0 ifTrue:
- 							[objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
- 								[objectRepresentation markAndTraceLiteralIfYoung: class].
- 							 mixin := backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop.
- 							 objectRepresentation markAndTraceLiteralIfYoung: mixin]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>maybeAllocAndInitIRCs (in category 'newspeak support') -----
  maybeAllocAndInitIRCs
  	"If this is the Newspeak VM and the objectRepresentation supports pinning
  	 then allocate space for the implicit receiver caches on the heap."
  	self cppIf: #NewspeakVM
  		ifTrue:
  			[indexOfIRC := theIRCs := 0.
  			 (objectRepresentation canPinObjects and: [numIRCs > 0]) ifTrue:
  				[self assert: (self noAssertMethodClassAssociationOf: methodObj) ~= objectMemory nilObject.
+ 				 theIRCs := objectRepresentation allocateNPinnedSlots: numIRCs * NumOopsPerNSC.
- 				 theIRCs := objectRepresentation allocateNPinnedSlots: numIRCs * NumOopsPerIRC.
  				 ^theIRCs ~= 0].
  			 ^true]
  		ifFalse:
  			[^true]!

Item was added:
+ ----- Method: Cogit>>nsSendCacheFromReturnAddress: (in category 'newspeak support') -----
+ nsSendCacheFromReturnAddress: mcpc
+ 	"Caller looks like
+ 			mov LcacheAddress, SendNumArgsReg
+ 			call ceImplicitReceiver"
+ 	<option: #NewspeakVM>
+ 	<var: #mcpc type: #'char *'>
+ 	<inline: true>
+ 	| entryPoint cacheAddress |
+ 	entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 	self assert: entryPoint < methodZoneBase.
+ 	cacheAddress := (backEnd implicitReceiveCacheAt: mcpc) asUnsignedInteger.
+ 	self assert: (objectMemory isInOldSpace: cacheAddress).
+ 	^self cCoerceSimple: cacheAddress to: #'NSSendCache *'
+ !

Item was added:
+ ----- Method: Cogit>>nsSendCacheSurrogateAt: (in category 'simulation only') -----
+ nsSendCacheSurrogateAt: address
+ 	<doNotGenerate>
+ 	self assert: (address < 0 or: [(address bitAnd: objectMemory wordSize - 1) = 0]).
+ 	^nsSendCacheSurrogateClass new
+ 		at: address
+ 		objectMemory: objectMemory
+ 		cogit: self!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: delta
  	<var: #mcpc type: #'char *'>
+ 	| entryPoint offset sendTable targetMethod unlinkedRoutine nsSendCache |
- 	| entryPoint offset sendTable targetMethod unlinkedRoutine |
  	<var: #sendTable type: #'sqInt *'>
  	<var: #targetMethod type: #'CogMethod *'>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 
+ 	self cppIf: NewspeakVM ifTrue: [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"
+ 					[nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
+ 		^0]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
- 		 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: [:off :table| offset := off. sendTable := table].
  		 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
  		 targetMethod cmType = CMMethod ifTrue: "send target not freed; just relocate."
  			[backEnd
  				relocateCallBeforeReturnPC: mcpc asInteger
  				by: (delta - targetMethod objectHeader) negated.
  			 ^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 *'>
+ 	| nsSendCache |
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[ | oop mappedOop |
+ 		nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		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"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	(self isSendAnnotation: 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 asInteger.
  					 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 into:
+ 						[:targetMethod :ignored|
+ 						 (objectMemory isYoung: targetMethod selector) ifTrue:
+ 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
- 			 (self cppIf: NewspeakVM
- 					ifTrue: [entryPoint = ceImplicitReceiverTrampoline]
- 					ifFalse: [false])
- 				ifTrue: "Examine an implicit receiver cache."
- 					[| cacheAddress oop mappedOop |
- 					 self assert: NumOopsPerIRC = 2.
- 					 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 					 (oop := backEnd unalignedLongAt: cacheAddress) ~= 0 ifTrue:
- 						["First look at the classTag entry.  This is an inline cache tag and so might not be an object."
- 						 (objectRepresentation inlineCacheTagsMayBeObjects
- 						  and: [objectRepresentation couldBeObject: oop]) ifTrue:
- 							[mappedOop := objectRepresentation remapOop: oop.
- 							 mappedOop ~= oop ifTrue:
- 								[backEnd unalignedLongAt: cacheAddress put: mappedOop].
- 							 (hasYoungPtr ~= 0
- 							  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
- 						 "Second look at the mixin entry. this must be 0 or an object."
- 						 (oop := backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop) ~= 0 ifTrue:
- 							[mappedOop := objectRepresentation remapOop: oop.
- 							 mappedOop ~= oop ifTrue:
- 								[backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: mappedOop].
- 							 (hasYoungPtr ~= 0
- 							  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
- 				ifFalse:
- 					[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 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>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
  	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := 8. "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	breakBlock ifNil: [self breakPC: breakPC].
  	(backEnd := processor abstractInstructionCompilerClass new) cogit: self.
  	(methodLabel := processor abstractInstructionCompilerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
+ 		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
+ 		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
- 		 dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	compilationTrace ifNil: [compilationTrace := 0].
  	extA := extB := 0!

Item was changed:
  ----- Method: Cogit>>unlinkIfForwardedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfForwardedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
+ 	<var: #nsSendCache type: #'NSSendCache *'>
+ 	| entryPoint nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		nsSendCache classTag ~= 0 ifTrue:
+ 			[(objectMemory isForwardedClassIndex: nsSendCache classTag) ifTrue: [
+ 				nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
+ 		"Should we check if the enclosing object's class is forwarded as well?"
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint cacheAddress |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
  				[(objectMemory isForwardedClassIndex: (backEnd inlineCacheTagAt: mcpc asInteger)) ifTrue:
  					[self targetMethodAndSendTableFor: entryPoint into:
  						[:targetMethod :sendTable|
+ 						 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
+ 
- 						 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 			ifFalse:
- 				[self cppIf: NewspeakVM ifTrue:
- 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 						[self assert: NumOopsPerIRC = 2.
- 						 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 						 ((objectMemory isForwardedClassIndex: (backEnd unalignedLongAt: cacheAddress))
- 						 or: [objectMemory isForwardedClassIndex: (backEnd unalignedLongAt: cacheAddress + objectMemory bytesPerOop)]) ifTrue:
- 							[self voidImplicitReceiverCacheAt: mcpc]]]]].
  	^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 nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [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:
+ 				[nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
  					[:targetMethod :sendTable| 
  					 (targetMethod cmType = CMFree
  					  or: [targetMethod selector = theSelector]) ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
+ 
- 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 			ifFalse:
- 				[self cppIf: NewspeakVM ifTrue:
- 					[(entryPoint = ceImplicitReceiverTrampoline
- 					 and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
- 					 	[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^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 nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		nsSendCache classTag ~= 0 ifTrue: "Send is linked"
+ 			[nsSendCache classTag: 0; enclosingObject: 0; target: 0].
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
  					[:targetMethod :sendTable| 
+ 					 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]].
+ 
- 					 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]
- 			ifFalse:
- 				[self cppIf: NewspeakVM ifTrue:
- 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^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 nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		nsSendCache selector = theSelector ifTrue:
+ 			[nsSendCache classTag: 0; enclosingObject: 0; target: 0].
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
  					[:targetMethod :sendTable| 
  					 targetMethod selector = theSelector ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
+ 
- 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 			ifFalse:
- 				[self cppIf: NewspeakVM ifTrue:
- 					[(entryPoint = ceImplicitReceiverTrampoline
- 					  and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
- 						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^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 nsSendCache |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
+ 		[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		(entryPoint := nsSendCache target) ~= 0 ifTrue:
+ 			[ | targetMethod |
+ 			targetMethod := entryPoint - cmNoCheckEntryOffset.
+ 			targetMethod = theCogMethod ifTrue:
+ 				[nsSendCache classTag: 0.
+ 				nsSendCache enclosingObject: 0.
+ 				nsSendCache target: 0]].
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
  					[:targetMethod :sendTable| 
  					 targetMethod asInteger = theCogMethod ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
+ 
- 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 			ifFalse: "Can't tell the target with PushReciver/SendImplicit so flush anyway."
- 				[self cppIf: NewspeakVM ifTrue:
- 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^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 nsSendCache nsTargetMethod |
+ 
+ 	self cppIf: NewspeakVM ifTrue: [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:
+ 				[nsSendCache classTag: 0.
+ 				nsSendCache enclosingObject: 0.
+ 				nsSendCache target: 0]].
+ 		^0 "keep scanning"]].
+ 
+ 	annotation = IsSendCall ifTrue:
- 	| entryPoint |
- 	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint into:
  				[:targetMethod :sendTable| 
  				 targetMethod cmType = CMFree ifTrue:
  					[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
+ 
  	^0 "keep scanning"!

Item was removed:
- ----- Method: Cogit>>voidImplicitReceiverCacheAt: (in category 'newspeak support') -----
- voidImplicitReceiverCacheAt: mcpc
- 	"Cached push implicit receiver implementation.  If objectRepresentation doesn't support
- 	 pinning then caller looks like
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 				br continue
- 		Lclass:	.word
- 		Lmixin::	.word
- 		continue:
- 	 If objectRepresentation supports pinning then caller looks like
- 				mov Lclass, Arg1Reg
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 	 and Lclass: .word; Lmixin: .word is somewhere on the heap."
- 	<option: #NewspeakVM>
- 	<var: #mcpc type: #'char *'>
- 	| cacheAddress |
- 	self assert: NumOopsPerIRC = 2.
- 	cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
- 	backEnd
- 		unalignedLongAt: cacheAddress put: 0;
- 		unalignedLongAt: cacheAddress + objectMemory bytesPerOop put: 0.
- 	objectRepresentation canPinObjects ifFalse:
- 		[codeModified := true]!

Item was added:
+ VMStructType subclass: #NSSendCache
+ 	instanceVariableNames: 'selector numArgs classTag enclosingObject target'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'CogMethodConstants VMBasicConstants'
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: NSSendCache class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"self initialize"
+ 	(Smalltalk classNamed: #NSSendCacheSurrogate32) ifNotNil:
+ 		[:scs32|
+ 		self checkGenerateSurrogate: scs32 bytesPerWord: 4].
+ 	(Smalltalk classNamed: #NSSendCacheSurrogate64) ifNotNil:
+ 		[:scs64|
+ 		self checkGenerateSurrogate: scs64 bytesPerWord: 8]!

Item was added:
+ ----- Method: NSSendCache class>>instVarNamesAndTypesForTranslationDo: (in category 'as yet unclassified') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 
+ 	self allInstVarNames do:
+ 		[:ivn| aBinaryBlock
+ 				value: ivn
+ 				value: #'sqInt']!

Item was added:
+ ----- Method: NSSendCache>>classTag (in category 'accessing') -----
+ classTag
+ 
+ 	^ classTag!

Item was added:
+ ----- Method: NSSendCache>>classTag: (in category 'accessing') -----
+ classTag: anObject
+ 
+ 	^classTag := anObject!

Item was added:
+ ----- Method: NSSendCache>>enclosingObject (in category 'accessing') -----
+ enclosingObject
+ 
+ 	^ enclosingObject!

Item was added:
+ ----- Method: NSSendCache>>enclosingObject: (in category 'accessing') -----
+ enclosingObject: anObject
+ 
+ 	^enclosingObject := anObject!

Item was added:
+ ----- Method: NSSendCache>>numArgs (in category 'accessing') -----
+ numArgs
+ 
+ 	^ numArgs!

Item was added:
+ ----- Method: NSSendCache>>numArgs: (in category 'accessing') -----
+ numArgs: anObject
+ 
+ 	^numArgs := anObject!

Item was added:
+ ----- Method: NSSendCache>>selector (in category 'accessing') -----
+ selector
+ 
+ 	^ selector!

Item was added:
+ ----- Method: NSSendCache>>selector: (in category 'accessing') -----
+ selector: anObject
+ 
+ 	^selector := anObject!

Item was added:
+ ----- Method: NSSendCache>>target (in category 'accessing') -----
+ target
+ 
+ 	^ target!

Item was added:
+ ----- Method: NSSendCache>>target: (in category 'accessing') -----
+ target: anObject
+ 
+ 	^target := anObject!

Item was added:
+ VMClass subclass: #NSSendCacheSurrogate
+ 	instanceVariableNames: 'address memory cogit'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: NSSendCacheSurrogate>>at:objectMemory:cogit: (in category 'as yet unclassified') -----
+ at: anAddress objectMemory: objectMemory cogit: aCogit
+ 	address := anAddress.
+ 	memory := objectMemory memory.
+ 	cogit := aCogit!

Item was added:
+ NSSendCacheSurrogate subclass: #NSSendCacheSurrogate32
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: NSSendCacheSurrogate32 class>>alignedByteSize (in category 'as yet unclassified') -----
+ alignedByteSize
+ 	^20!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>classTag (in category 'as yet unclassified') -----
+ classTag
+ 	^memory unsignedLongAt: address + 9!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>classTag: (in category 'accessing') -----
+ classTag: aValue
+ 	^memory
+ 		unsignedLongAt: address + 9
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>enclosingObject (in category 'as yet unclassified') -----
+ enclosingObject
+ 	^memory unsignedLongAt: address + 13!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>enclosingObject: (in category 'accessing') -----
+ enclosingObject: aValue
+ 	^memory
+ 		unsignedLongAt: address + 13
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>numArgs (in category 'as yet unclassified') -----
+ numArgs
+ 	^memory unsignedLongAt: address + 5!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>numArgs: (in category 'accessing') -----
+ numArgs: aValue
+ 	^memory
+ 		unsignedLongAt: address + 5
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>selector (in category 'as yet unclassified') -----
+ selector
+ 	^memory unsignedLongAt: address + 1!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>selector: (in category 'accessing') -----
+ selector: aValue
+ 	^memory
+ 		unsignedLongAt: address + 1
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>target (in category 'as yet unclassified') -----
+ target
+ 	^memory unsignedLongAt: address + 17!

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>target: (in category 'accessing') -----
+ target: aValue
+ 	^memory
+ 		unsignedLongAt: address + 17
+ 		put: aValue!

Item was added:
+ NSSendCacheSurrogate subclass: #NSSendCacheSurrogate64
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: NSSendCacheSurrogate64 class>>alignedByteSize (in category 'as yet unclassified') -----
+ alignedByteSize
+ 	^40!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>classTag (in category 'accessing') -----
+ classTag
+ 	^memory unsignedLongLongAt: address + 17!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>classTag: (in category 'accessing') -----
+ classTag: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 17
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>enclosingObject (in category 'accessing') -----
+ enclosingObject
+ 	^memory unsignedLongLongAt: address + 25!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>enclosingObject: (in category 'accessing') -----
+ enclosingObject: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 25
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>numArgs (in category 'accessing') -----
+ numArgs
+ 	^memory unsignedLongLongAt: address + 9!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>numArgs: (in category 'accessing') -----
+ numArgs: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 9
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>selector (in category 'accessing') -----
+ selector
+ 	^memory unsignedLongLongAt: address + 1!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>selector: (in category 'accessing') -----
+ selector: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 1
+ 		put: aValue!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>target (in category 'accessing') -----
+ target
+ 	^memory unsignedLongLongAt: address + 33!

Item was added:
+ ----- Method: NSSendCacheSurrogate64>>target: (in category 'accessing') -----
+ target: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 33
+ 		put: aValue!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	FirstSpecialSelector := 176.
  	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    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
+ 		(3 126 126 unknownBytecode)		"Was non-absent Newspeak super"
+ 		(2 127 127 unknownBytecode)		"Was push implicit receiver"
- 		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
- 		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
+ 		(2 138 138 genPushNewArrayBytecode)
- 		(2 138 138 genPushNewArrayBytecode)),
  
+ 		(3 139 139 callPrimitiveBytecode)
- 		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
- 			ifTrue: [#((3 139 139 callPrimitiveBytecode))]									"V3PlusClosures on Spur"
- 			ifFalse: [#((2 139 139 genPushEnclosingObjectBytecode isMapped))]),	"Newspeak"
- 
- 	  #(
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	NumTrampolines := NewspeakVM
+ 							ifTrue: [56]
- 							ifTrue: [53]
  							ifFalse: [42]!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genDynamicSuperSendBytecode (in category 'bytecode generators') -----
- genDynamicSuperSendBytecode
- 	^self genSendDynamicSuper: (self getLiteral: byte2) numArgs: byte1!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genGetImplicitReceiverFor:forPush: (in category 'bytecode generators') -----
- genGetImplicitReceiverFor: selector forPush: forPushSendBar
- 	"Cached implicit receiver implementation.  If objectRepresentation doesn't support
- 	 pinning then caller looks like
- 				mov selector, ClassReg
- 				call ceImplicitReceiverTrampoline
- 				br continue
- 		Lclass	.word
- 		Lmixin:	.word
- 		continue:
- 	 If objectRepresentation supports pinning then caller looks like
- 				mov Lclass, Arg1Reg
- 				mov selector, SendNumArgsReg
- 				call ceImplicitReceiver
- 	 and Lclass: .word; Lmixin: .word is somewhere on the heap.
- 
- 	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
- 	 If 0, answer the actual receiver.  This is done in the trampoline.
- 	 See generateNewspeakRuntime."
- 
- 	| skip |
- 	<var: #skip type: #'AbstractInstruction *'>
- 	"N.B. For PC mapping either this is used for SendAbsentImplicit or for PushAbsentReceiver
- 	 but not both.  So any Newspeak instruction set has to choose either SendAbsentImplicit
- 	 or PushImplicitReceiver.  See isPCMappedAnnotation:alternateInstructionSet:"
- 	self assert: forPushSendBar = (self isPCMappedAnnotation: IsNSSendCall
- 										alternateInstructionSet: bytecodeSetOffset > 0).
- 	self assert: (self noAssertMethodClassAssociationOf: methodObj) ~= objectMemory nilObject.
- 	self assert: needsFrame.
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	objectRepresentation canPinObjects ifTrue:
- 		[self MoveCw: theIRCs + (2 * objectMemory bytesPerOop * indexOfIRC) R: Arg1Reg.
- 		 self MoveCw: selector R: SendNumArgsReg.
- 		 self CallNewspeakSend: ceImplicitReceiverTrampoline.
- 		 indexOfIRC := indexOfIRC + 1.
- 		 ^0].
- 	self MoveCw: selector R: SendNumArgsReg.
- 	self CallNewspeakSend: ceImplicitReceiverTrampoline.
- 	skip := self Jump: 0.
- 	self Fill32: 0.
- 	self Fill32: 0.
- 	skip jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushImplicitReceiverBytecode (in category 'bytecode generators') -----
- genPushImplicitReceiverBytecode
- 	| result |
- 	result := self genGetImplicitReceiverFor: (self getLiteral: byte1) forPush: true.
- 	result ~= 0 ifTrue:
- 		[^result].
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
  genSendAbsentImplicit: selector numArgs: numArgs
+ 	| nsSendCache |
- 	"Get the implicit receiver and shuffle arguments if necessary.
- 	 Then send."
  	<inline: false>
+ 	(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.
+ 
+ 	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
+ 
+ 	"This leaves the method receiver on the stack, which might not be the implicit receiver. But we care
+ 	 not: the callee will use ReceiverResultReg to build its frame, not the value beneath the arguments."
- 	| result |
- 	result := self genGetImplicitReceiverFor: selector forPush: false.
- 	result ~= 0 ifTrue:
- 		[^result].
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (implicitReceiverSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	self PushR: ReceiverResultReg.
+ 	^0!
- 	^self genSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: SpurMemoryManager>>isInOldSpace: (in category 'object testing') -----
  isInOldSpace: address
+ 	<api>
  	^self
  		oop: address
  		isGreaterThanOrEqualTo: oldSpaceStart
  		andLessThan: endOfMemory!

Item was added:
+ ----- Method: StackDepthFinder>>sendToAbsentOuter:numArgs:depth: (in category 'instruction decoding') -----
+ sendToAbsentOuter: selector numArgs: numArgs depth: depth
+ 	self drop: numArgs - 1 "e.g. if no args pushes a result"!

Item was added:
+ ----- Method: StackDepthFinder>>sendToAbsentSelf:numArgs: (in category 'instruction decoding') -----
+ sendToAbsentSelf: selector numArgs: numArgs
+ 	self drop: numArgs - 1 "e.g. if no args pushes a result"!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	FirstSpecialSelector := 176.
  	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    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
+ 		(3 126 126 unknownBytecode)		"Was non-absent Newspeak super send"
+ 		(2 127 127 unknownBytecode)		"Was push implicit receiver"
- 		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
- 		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
+ 		(2 138 138 genPushNewArrayBytecode)
- 		(2 138 138 genPushNewArrayBytecode)),
  
+ 		(3 139 139 callPrimitiveBytecode)
- 		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
- 			ifTrue: [#((3 139 139 callPrimitiveBytecode))]									"V3PlusClosures on Spur"
- 			ifFalse: [#((2 139 139 genPushEnclosingObjectBytecode isMapped))]),	"Newspeak"
- 
- 	  #(
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:.
+ 	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
- 	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 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 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)
  		(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)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode)
  		(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)
  
  		(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)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 callPrimitiveBytecode)
  		(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)
  
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	NumTrampolines := NewspeakVM
+ 							ifTrue: [66]
- 							ifTrue: [63]
  							ifFalse: [52]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genGetImplicitReceiverFor:forPush: (in category 'bytecode generators') -----
- genGetImplicitReceiverFor: selector forPush: forPushSendBar
- 	"Cached implicit receiver implementation.  Caller looks like
- 		mov selector, ClassReg
- 				call cePushImplicitReceiver
- 				br continue
- 		Lclass	.word
- 		Lmixin:	.word
- 		continue:
- 	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
- 	 If 0, answer the actual receiver.  This is done in the trampoline.
- 	 See generateNewspeakRuntime."
- 	self ssAllocateCallReg: SendNumArgsReg and: ReceiverResultReg and: ClassReg and: Arg1Reg.
- 	^super genGetImplicitReceiverFor: selector forPush: forPushSendBar!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushImplicitReceiverBytecode (in category 'bytecode generators') -----
- genPushImplicitReceiverBytecode
- 	| result |
- 	result := self genGetImplicitReceiverFor: (self getLiteral: byte1) forPush: true.
- 	result ~= 0 ifTrue:
- 		[^result].
- 	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
  genSendAbsentImplicit: selector numArgs: numArgs
+ 	| nsSendCache |
- 	"Get the implicit receiver and marshall arguments, shuffling the
- 	 stack to push the implicit receiver if necessary. Then send."
  	<inline: false>
+ 	(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.
+ 
+ 	self ssAllocateCallReg: ReceiverResultReg and: SendNumArgsReg.
+ 	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
+ 
+ 	"This leaves the method receiver on the stack, which might not be the implicit receiver. But we care
+ 	 not: the callee will use ReceiverResultReg to build its frame, not the value beneath the arguments."
- 	| result |
- 	"This must not be PC-mapped"
- 	result := self genGetImplicitReceiverFor: selector forPush: false.
- 	result ~= 0 ifTrue:
- 		[^result].
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (implicitReceiverSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	optStatus isReceiverResultRegLive: false.
+ 	^self ssPushRegister: ReceiverResultReg!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!

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

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 - 2 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: numArgs)].
  	ordinarySendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					numArgs: self numRegArgs + 1
  					called: (self trampolineName: 'ceSend' numArgs: -1)
  					arg: ClassReg
  					arg: 0
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
+ 
+ 	"Generate these in the middle so they are within [firstSend, lastSend]."
+ 	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
+ 
- 	self cppIf: NewspeakVM
- 		ifTrue:
- 			[0 to: NumSendTrampolines - 2 do:
- 				[:numArgs|
- 				dynamicSuperSendTrampolines
- 					at: numArgs
- 					put: (self genSendTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 							  numArgs: numArgs
- 							  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
- 							  arg: ClassReg
- 							  arg: ReceiverResultReg
- 							  arg: numArgs)].
- 			dynamicSuperSendTrampolines
- 				at: NumSendTrampolines - 1
- 				put: (self genSendTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 							numArgs: self numRegArgs + 1
- 							called: (self trampolineName: 'ceDynSuperSend' numArgs: -1)
- 							arg: ClassReg
- 							arg: ReceiverResultReg
- 							arg: SendNumArgsReg).
- 			0 to: NumSendTrampolines - 2 do:
- 				[:numArgs|
- 				selfSendTrampolines
- 					at: numArgs
- 					put: (self genSendTrampolineFor: #ceSelfSend:to:numArgs:
- 							  numArgs: numArgs
- 							  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
- 							  arg: ClassReg
- 							  arg: ReceiverResultReg
- 							  arg: numArgs)].
- 			selfSendTrampolines
- 				at: NumSendTrampolines - 1
- 				put: (self genSendTrampolineFor: #ceSelfSend:to:numArgs:
- 							numArgs: self numRegArgs + 1
- 							called: (self trampolineName: 'ceSelfSend' numArgs: -1)
- 							arg: ClassReg
- 							arg: ReceiverResultReg
- 							arg: SendNumArgsReg)].
  	0 to: NumSendTrampolines - 2 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: numArgs)].
  	superSendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					numArgs: self numRegArgs + 1
  					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
  					arg: ClassReg
  					arg: 1
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!



More information about the Vm-dev mailing list