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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 31 00:42:27 UTC 2015


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

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

Name: VMMaker.oscog-eem.1131
Author: eem
Time: 30 March 2015, 5:40:05.693 pm
UUID: 5b810f83-978b-4275-999c-61ed1a9a39d8
Ancestors: VMMaker.oscog-eem.1130

Integrate Ryan's SelfSends (new self send
entry-point) code.

Refactor send generation to take the send table to use
as an argument.  rename sendTable to ordinarySendTable.

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

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

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 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'
- 	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 sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs'
  	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>>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' 'dynSuperEntry' 'dynSuperEntryAlignment'
+ 			'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'ceImplicitReceiverTrampoline'
+ 			'ceEnclosingObjectTrampoline' 'cmSelfSendEntryOffset' 'cmDynSuperEntryOffset'
- 		[#(	'dynSuperEntry' 'dynSuperEntryAlignment' 'dynamicSuperSendTrampolines'
- 			'ceImplicitReceiverTrampoline' 'ceEnclosingObjectTrampoline' '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"';
  		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 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: #sendTrampolines
- 			declareC: 'sqInt sendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
+ 		var: #selfSendTrampolines
+ 			declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[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>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[self assert: (targetMethod asInteger + cmEntryOffset = entryPoint
+ 					or: [targetMethod asInteger + cmSelfSendEntryOffset = entryPoint
+ 					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]]).
- 					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]).
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
+ 		 targetMethod asInteger + cmSelfSendEntryOffset = entryPoint ifTrue:
+ 			[^coInterpreter
+ 				ceSelfSend: targetMethod selector
+ 				to: receiver
+ 				numArgs: targetMethod cmNumArgs].
  		 targetMethod asInteger + cmDynSuperEntryOffset = entryPoint ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asInteger to: pic asInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  	processor flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>compileCPICEntry (in category 'in-line cacheing') -----
  compileCPICEntry
  	<returnTypeC: #'AbstractInstruction *'>
  	"Compile the cache tag computation and the first comparison.  Answer the address of that comparison."
  	self cppIf: NewspeakVM ifTrue:
+ 		[self Nop. "1st nop differentiates from no-check entry if using nextMethod"
+ 		 selfSendEntry := self Nop.
- 		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
  		 dynSuperEntry := self Nop].
  	entry := objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: TempReg forEntry: true.
  	self CmpR: ClassReg R: TempReg.
  	^self JumpNonZero: 0!

Item was changed:
  ----- Method: Cogit>>compileEntry (in category 'compile abstract instructions') -----
  compileEntry
  	"The entry code to a method checks that the class of the current receiver matches
  	 that in the inline cache.  Other non-obvious elements are that its alignment must be
  	 different from the alignment of the noCheckEntry so that the method map machinery
  	 can distinguish normal and super sends (super sends bind to the noCheckEntry).
+ 	 In Newspeak we also need to distinguish dynSuperSends and self sends from normal
+ 	 and super sends and so on Newspeak, bind the dynSuperEntry and selfSendEntry to
+ 	 preceeding nops (on x86 there happens to be at least one anyway)."
- 	 In Newspeak we also need to distinguish dynSuperSends from normal and super
- 	 and so on Nespeak, bind the dynSuperEntry to the preceeding nop (on x86 there
- 	 happens to be one anyway)."
  
  	self cppIf: NewspeakVM ifTrue:
+ 		[self Nop. "1st nop differentiates from no-check entry if using nextMethod".
+ 		 dynSuperEntry := self Nop.
+ 		 selfSendEntry := self Nop]. "Put selfSend last as it has higher dynamic frequency."
- 		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
- 		 dynSuperEntry := self Nop].
  	entry := objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: TempReg forEntry: true.
  	self CmpR: ClassReg R: TempReg.
  	self JumpNonZero: sendMiss.
  	noCheckEntry := self Label.
  	self compileSendTrace ifTrue:
  		[backEnd saveAndRestoreLinkRegAround:
  			[self CallRT: ceTraceLinkedSendTrampoline]]!

Item was changed:
  ----- Method: Cogit>>computeEntryOffsets (in category 'initialization') -----
  computeEntryOffsets
  	"Generate the entry code for a method to determine cmEntryOffset and cmNoCheckEntryOffset.  We
  	 need cmNoCheckEntryOffset up front to be able to generate the map starting from cmNoCheckEntryOffset"
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	| sendMissCall |
  	<var: 'sendMissCall' type: #'AbstractInstruction *'>
  	self allocateOpcodes: 24 bytecodes: 0.
  	methodOrBlockNumArgs := 0.
  	sendMissCall := self compileAbort.
  	self compileEntry.
  	self computeMaximumSizes.
  	self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	cmEntryOffset := entry address - methodZoneBase.
  	cmNoCheckEntryOffset := noCheckEntry address - methodZoneBase.
+ 	self cppIf: NewspeakVM ifTrue:
+ 		[cmSelfSendEntryOffset := selfSendEntry address - methodZoneBase.
+ 		 cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase].
- 	self cppIf: NewspeakVM
- 		ifTrue: [cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase].
  	missOffset := sendMissCall address + sendMissCall machineCodeSize - methodZoneBase.
  	entryPointMask := objectMemory wordSize - 1.
  	[self cppIf: NewspeakVM
  		ifTrue: [(cmEntryOffset bitAnd: entryPointMask) = (cmNoCheckEntryOffset bitAnd: entryPointMask)
+ 				or: [(cmEntryOffset bitAnd: entryPointMask) = (cmSelfSendEntryOffset bitAnd: entryPointMask)
  				or: [(cmEntryOffset bitAnd: entryPointMask) = (cmDynSuperEntryOffset bitAnd: entryPointMask)
+ 				or: [(cmNoCheckEntryOffset bitAnd: entryPointMask) = (cmDynSuperEntryOffset bitAnd: entryPointMask)]]]]
- 				or: [(cmNoCheckEntryOffset bitAnd: entryPointMask) = (cmDynSuperEntryOffset bitAnd: entryPointMask)]]]
  		ifFalse: [(cmEntryOffset bitAnd: entryPointMask) = (cmNoCheckEntryOffset bitAnd: entryPointMask)]] whileTrue:
  		[entryPointMask := entryPointMask + entryPointMask + 1].
  	entryPointMask >= (methodZone roundUpLength: 1) ifTrue:
  		[self error: 'cannot differentiate checked and unchecked entry-points with current cog method alignment'].
  	checkedEntryAlignment := cmEntryOffset bitAnd: entryPointMask.
  	uncheckedEntryAlignment := cmNoCheckEntryOffset bitAnd: entryPointMask.
  	self assert: checkedEntryAlignment ~= uncheckedEntryAlignment.
  	self cppIf: NewspeakVM
  		ifTrue:
+ 			[cmSelfSendEntryOffset := selfSendEntry address - methodZoneBase.
+ 			 selfSendEntryAlignment := cmSelfSendEntryOffset bitAnd: entryPointMask.
+ 			 cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase.
- 			[cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase.
  			 dynSuperEntryAlignment := cmDynSuperEntryOffset bitAnd: entryPointMask.
+ 			self assert: selfSendEntryAlignment ~= checkedEntryAlignment.
+ 			self assert: selfSendEntryAlignment ~= uncheckedEntryAlignment.
  			self assert: dynSuperEntryAlignment ~= checkedEntryAlignment.
+ 			self assert: dynSuperEntryAlignment ~= uncheckedEntryAlignment.
+ 			self assert: dynSuperEntryAlignment ~= selfSendEntryAlignment]!
- 			self assert: dynSuperEntryAlignment ~= uncheckedEntryAlignment]!

Item was changed:
  ----- Method: Cogit>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
  	| cogMethod mapEntries codeRanges |
  	cogMethod := surrogateOrAddress isInteger
  								ifTrue: [self cogMethodSurrogateAt: surrogateOrAddress]
  								ifFalse: [surrogateOrAddress].
  	cogMethod cmType = CMBlock ifTrue:
  		[^self disassembleMethod: cogMethod cmHomeMethod on: aStream].
  	self printMethodHeader: cogMethod on: aStream.
  
  	(mapEntries := Dictionary new)
  		at: cogMethod asInteger + cmEntryOffset put: 'entry'.
  	
  	cogMethod cmType = CMMethod ifTrue:
  		[mapEntries at: cogMethod asInteger + cmNoCheckEntryOffset put: 'noCheckEntry'.
+ 		self cppIf: NewspeakVM ifTrue:
+ 			[mapEntries at: cogMethod asInteger + selfSendEntryAlignment put: 'selfSendEntry'.
+ 			mapEntries at: cogMethod asInteger + dynSuperEntryAlignment put: 'dynSuperEntry']].
- 		self cppIf: NewspeakVM
- 			ifTrue: [mapEntries at: cogMethod asInteger + dynSuperEntryAlignment put: 'dynSuperEntry']].
  
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[mapEntries at: cogMethod asInteger + firstCPICCaseOffset put: 'ClosedPICCase0'.
  		 1 to: numPICCases - 1 do:
  			[:i|
  			mapEntries
  				at: cogMethod asInteger + firstCPICCaseOffset + (i * cPICCaseSize)
  				put: 'ClosedPICCase', i printString]].
  
  	self mapFor: cogMethod
  		performUntil: #collectMapEntry:address:into:
  		arg: mapEntries.
  
  	self cppIf: NewspeakVM
  		ifTrue:
  			[objectRepresentation canPinObjects ifFalse:
  				[mapEntries keys do:
  					[:a|
  					(mapEntries at: a) = #IsNSSendCall ifTrue:
  						[mapEntries
  							at: a + backEnd jumpShortByteSize
  								put: {'Class'. #disassembleCachedOop:. (objectMemory wordSize)};
  							at: a + backEnd jumpShortByteSize + objectMemory bytesPerOop
  								put: {'ImplicitReceiver'. #disassembleCachedOop:. (objectMemory wordSize)}]]]].
  
  	"This would all be far more elegant and simple if we used blocks.
  	 But there are no blocks in C and the basic enumerators here need
  	 to be used in the real VM.  Apologies."
  	(codeRanges := self codeRangesFor: cogMethod) do:
  		[:range|
  		(cogMethod cmType = CMMethod) ifTrue:
  			[mapEntries keysAndValuesDo:
  				[:mcpc :label| | bcpc |
  				((range includes: mcpc)
  				 and: [(#(IsSendCall HasBytecodePC) includes: label)
  				 and: [range cogMethod stackCheckOffset > 0]]) ifTrue:
  					[bcpc := self bytecodePCFor: mcpc startBcpc: range startpc in: range cogMethod.
  					 bcpc ~= 0 ifTrue:
  						[mapEntries at: mcpc put: label, ' bc ', bcpc printString, '/', (bcpc + 1) printString]]]].
  		(cogMethod blockEntryOffset ~= 0
  		 and: [range first = (cogMethod blockEntryOffset + cogMethod asInteger)])
  			ifTrue:
  				[aStream nextPutAll: 'blockEntry:'; cr.
  				 self blockDispatchFor: cogMethod
  					perform: #disassemble:from:to:arg:
  					arg: aStream]
  			ifFalse:
  				[range first > (cogMethod address + cmNoCheckEntryOffset) ifTrue:
  					[self printMethodHeader: range cogMethod
  						on: aStream].
  				self disassembleFrom: range first to: range last labels: mapEntries on: aStream]].
  	aStream nextPutAll: 'startpc: '; print: codeRanges first startpc; cr.
  	(cogMethod cmType = CMMethod
  	 or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  		[[self mapFor: cogMethod
  			performUntil: #printMapEntry:mcpc:args:
  			arg: { aStream. codeRanges. cogMethod }]
  			on: AssertionFailure
  			do: [:ex|
  				ex primitiveChangeClassTo: ResumableVMError basicNew. ":) :) :)"
  				ex resume: nil]].
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
+ 		ordinarySendTrampolines
- 		sendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: numArgs)].
+ 	ordinarySendTrampolines
- 	sendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					called: (self trampolineName: 'ceSend' numArgs: -1)
  					arg: ClassReg
  					arg: 0
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  	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.
- 	firstSend := sendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self cppIf: NewspeakVM
  		ifTrue: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset
+ 							or: [theEntryOffset = cmSelfSendEntryOffset
+ 							or: [theEntryOffset = cmDynSuperEntryOffset]]])]
- 							or: [theEntryOffset = cmDynSuperEntryOffset]])]
  		ifFalse: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset])].
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
  	(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag) ifTrue:
  		[methodZone ensureInYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
  	processor
  		flushICacheFrom: callSiteReturnAddress - 1 - extent
  		to: callSiteReturnAddress - 1!

Item was changed:
  ----- Method: Cogit>>offsetAndSendTableFor:annotation:into: (in category 'in-line cacheing') -----
  offsetAndSendTableFor: entryPoint annotation: annotation into: binaryBlock
  	"Find the relevant sendTable for a linked-send to entryPoint.  Do this based on the
  	 alignment of entryPoint.  N.B.  For Newspeak sends we don't need to distinguish
  	 between ceImplicitReceiver and the other sends since ceImplicitReceiver will
  	 never appear to be linked, so only three cases here."
  	<inline: true>
  	self cppIf: NewspeakVM
  		ifTrue:
  			[self assert: annotation = IsSendCall.
  			 (entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 				ifTrue: [binaryBlock value: cmEntryOffset value: ordinarySendTrampolines]
+ 				ifFalse: [(entryPoint bitAnd: entryPointMask) = selfSendEntryAlignment
+ 					ifTrue: [binaryBlock value: cmSelfSendEntryOffset value: selfSendTrampolines]
+ 					ifFalse: [(entryPoint bitAnd: entryPointMask) = dynSuperEntryAlignment
- 				ifTrue: [binaryBlock value: cmEntryOffset value: sendTrampolines]
- 				ifFalse:
- 					[(entryPoint bitAnd: entryPointMask) = dynSuperEntryAlignment
  						ifTrue: [binaryBlock value: cmDynSuperEntryOffset value: dynamicSuperSendTrampolines]
+ 						ifFalse: [binaryBlock value: cmNoCheckEntryOffset value: superSendTrampolines]]]]
- 						ifFalse: [binaryBlock value: cmNoCheckEntryOffset value: superSendTrampolines]]]
  		ifFalse:
  			[(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 				ifTrue: [binaryBlock value: cmEntryOffset value: ordinarySendTrampolines]
- 				ifTrue: [binaryBlock value: cmEntryOffset value: sendTrampolines]
  				ifFalse: [binaryBlock value: cmNoCheckEntryOffset value: superSendTrampolines]]!

Item was added:
+ ----- Method: Cogit>>selfSendEntryOffset (in category 'accessing') -----
+ selfSendEntryOffset
+ 	<api>
+ 	<cmacro: '() cmSelfSendEntryOffset'>
+ 	^cmSelfSendEntryOffset!

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).
- 	sendTrampolines := 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)].
- 		[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>>targetMethodAndSendTableFor:into: (in category 'in-line cacheing') -----
  targetMethodAndSendTableFor: entryPoint into: binaryBlock
  	"Evaluate binaryBlock with the targetMethod and relevant send table for a linked-send
  	 to entryPoint.  Do so based on the alignment of entryPoint.  N.B.  For Newspeak sends
  	 we don't need to distinguish between ceImplicitReceiver and the other sends since
  	 ceImplicitReceiver will never appear to be linked, so only three cases here."
  	<inline: true>
  	| targetMethod sendTable |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #sendTable type: #'sqInt *'>
  	self cppIf: NewspeakVM
  		ifTrue:
  			[(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
  				ifTrue:
  					[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
+ 					 sendTable := ordinarySendTrampolines]
+ 			ifFalse: [(entryPoint bitAnd: entryPointMask) = selfSendEntryAlignment
+ 				ifTrue:
+ 					[targetMethod := self cCoerceSimple: entryPoint - cmSelfSendEntryOffset to: #'CogMethod *'.
+ 					 sendTable := selfSendTrampolines]
+ 			ifFalse: [(entryPoint bitAnd: entryPointMask) = dynSuperEntryAlignment
+ 				ifTrue:
+ 					[targetMethod := self cCoerceSimple: entryPoint - cmDynSuperEntryOffset to: #'CogMethod *'.
+ 					 sendTable := dynamicSuperSendTrampolines]
- 					 sendTable := sendTrampolines]
  				ifFalse:
+ 					[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 					 sendTable := superSendTrampolines]]]]
- 					[(entryPoint bitAnd: entryPointMask) = dynSuperEntryAlignment
- 						ifTrue:
- 							[targetMethod := self cCoerceSimple: entryPoint - cmDynSuperEntryOffset to: #'CogMethod *'.
- 							 sendTable := dynamicSuperSendTrampolines]
- 						ifFalse:
- 							[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
- 							 sendTable := superSendTrampolines]]]
  		ifFalse:
  			[(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
  				ifTrue:
  					[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
+ 					 sendTable := ordinarySendTrampolines]
- 					 sendTable := sendTrampolines]
  				ifFalse:
  					[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  					 sendTable := superSendTrampolines]].
  	binaryBlock
  		value: targetMethod
  		value: sendTable!

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails."
  	| jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self compilePICAbort: numArgs.
  	self cppIf: NewspeakVM ifTrue:
  		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
+ 		 selfSendEntry := self Nop.
  		 dynSuperEntry := self Nop].
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  	self MoveR: ClassReg R: SendNumArgsReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	itsAHit := self Label.
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << objectMemory shiftForWord)
  		r: ClassReg
  		R: SendNumArgsReg.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation
  		genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
  	jumpBCMethod jmpTarget: picInterpretAbort.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	objectMemory shiftForWord > 2 ifTrue:
  		[self LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg].
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	backEnd genSaveStackPointers.
  	backEnd genLoadCStackPointers.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	self 
  		compileCallFor: #ceSendFromInLineCacheMiss:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: nil
  		saveRegs: false
  	"Note that this call does not return."!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs: (in category 'bytecode generators') -----
  genSend: selector numArgs: numArgs
+ 	<inline: true>
+ 	^self genSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	<inline: false>
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	self assert: needsFrame.
- 	self assert: (numArgs between: 0 and: 256). "say"
- 	self assert: (objectMemory addressCouldBeOop: selector).
- 	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
- 	numArgs > 2 ifTrue:
- 		[self MoveCq: numArgs R: SendNumArgsReg].
- 	self MoveCw: selector R: ClassReg.
- 	self CallSend: (sendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
- 	self flag: 'currently caller pushes result'.
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generators') -----
+ genSend: selector numArgs: numArgs sendTable: sendTable
+ 	<inline: false>
+ 	<var: #sendTable type: #'sqInt *'>
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 	self assert: needsFrame.
+ 	self assert: (numArgs between: 0 and: 256). "say"
+ 	self assert: (objectMemory addressCouldBeOop: selector).
+ 	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
+ 	numArgs > 2 ifTrue:
+ 		[self MoveCq: numArgs R: SendNumArgsReg].
+ 	self MoveCw: selector R: ClassReg.
+ 	self CallSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 	self flag: 'currently caller pushes result'.
+ 	self PushR: ReceiverResultReg.
+ 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genSendAbsentDynamicSuper: selector numArgs: numArgs
  	"Shuffle arguments if necessary and push receiver.
  	 Then send."
  	<inline: false>
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!
- 	^self genSendDynamicSuper: selector numArgs: numArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentSelf:numArgs: (in category 'bytecode generators') -----
  genSendAbsentSelf: selector numArgs: numArgs
  	"Shuffle arguments if necessary and push receiver.
  	 Then send."
  	<inline: false>
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genSend: selector numArgs: numArgs sendTable: selfSendTrampolines!
- 	^self genSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendSuper:numArgs: (in category 'bytecode generators') -----
  genSendSuper: selector numArgs: numArgs
  	<inline: false>
+ 	^self genSend: selector numArgs: numArgs sendTable: superSendTrampolines!
- 	self assert: needsFrame.
- 	self assert: (numArgs between: 0 and: 256). "say"
- 	self assert: (objectMemory addressCouldBeOop: selector).
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
- 	numArgs > 2 ifTrue:
- 		[self MoveCq: numArgs R: SendNumArgsReg].
- 	self MoveCw: selector R: ClassReg.
- 	self CallSend: (superSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
- 	self flag: 'currently caller pushes result'.
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst
  	  counterAddress countTripped |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genSpecialSelectorComparison ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
  		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  		 self annotateBytecodeIfAnnotated: self ssTop.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: objectMemory wordSize = CounterBytes.
  	self MoveAw: counterAddress R: SendNumArgsReg.
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
  	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
+ 		numArgs: 1
+ 		sendTable: ordinarySendTrampolines!
- 		numArgs: 1!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEquals
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  counterAddress countTripped unforwardArg unforwardRcvr |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genSpecialSelectorEqualsEquals ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	unforwardRcvr := (self ssValue: 1) type ~= SSConstant
  						or: [objectRepresentation shouldAnnotateObjectReference: (self ssValue: 1) constant].
  	unforwardArg := self ssTop type ~= SSConstant
  						or: [objectRepresentation shouldAnnotateObjectReference: self ssTop constant].
  	self marshallSendArguments: 1.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: objectMemory wordSize = CounterBytes.
  	self MoveAw: counterAddress R: SendNumArgsReg.
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
  	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  	unforwardRcvr ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	unforwardArg ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg].
  	self CmpR: Arg0Reg R: ReceiverResultReg.
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  	self MoveR: SendNumArgsReg Aw: counterAddress. "write back"
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: self Label.
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
+ 		numArgs: 1
+ 		sendTable: ordinarySendTrampolines!
- 		numArgs: 1!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails.
  	 Override to push the register args when calling ceSendFromInLineCacheMiss:"
  	| jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self compilePICAbort: numArgs.
  	self cppIf: NewspeakVM ifTrue:
  		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
+ 		 selfSendEntry := self Nop.
  		 dynSuperEntry := self Nop].
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  	self MoveR: ClassReg R: SendNumArgsReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	itsAHit := self Label.
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << objectMemory shiftForWord)
  		r: ClassReg
  		R: SendNumArgsReg.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation
  		genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
  	jumpBCMethod jmpTarget: picInterpretAbort.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	objectMemory shiftForWord > 2 ifTrue:
  		[self LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg].
  	self AndCq: MethodCacheMask << objectMemory shiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << objectMemory shiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForNumArgs: numArgs.
  	self genSmalltalkToCStackSwitch.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	self 
  		compileCallFor: #ceSendFromInLineCacheMiss:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: nil
  		saveRegs: false
  	"Note that this call does not return."!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs: (in category 'bytecode generators') -----
- genMarshalledSend: selector numArgs: numArgs
- 	<inline: false>
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	self assert: needsFrame.
- 	numArgs > 2 ifTrue:
- 		[self MoveCq: numArgs R: SendNumArgsReg].
- 	self MoveCw: selector R: ClassReg.
- 	self CallSend: (sendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
- 	optStatus isReceiverResultRegLive: false.
- 	^self ssPushRegister: ReceiverResultReg!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generators') -----
+ genMarshalledSend: selector numArgs: numArgs sendTable: sendTable
+ 	<inline: false>
+ 	<var: #sendTable type: #'sqInt *'>
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 	self assert: needsFrame.
+ 	numArgs > 2 ifTrue:
+ 		[self MoveCq: numArgs R: SendNumArgsReg].
+ 	self MoveCw: selector R: ClassReg.
+ 	self CallSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 	optStatus isReceiverResultRegLive: false.
+ 	^self ssPushRegister: ReceiverResultReg!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genMarshalledSendDynamicSuper:numArgs: (in category 'bytecode generators') -----
- genMarshalledSendDynamicSuper: selector numArgs: numArgs
- 	<inline: false>
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	self assert: needsFrame.
- 	numArgs > 2 ifTrue:
- 		[self MoveCq: numArgs R: SendNumArgsReg].
- 	self MoveCw: selector R: ClassReg.
- 	self CallSend: (dynamicSuperSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
- 	optStatus isReceiverResultRegLive: false.
- 	^self ssPushRegister: ReceiverResultReg!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genMarshalledSendSuper:numArgs: (in category 'bytecode generators') -----
- genMarshalledSendSuper: selector numArgs: numArgs
- 	<inline: false>
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
- 	self assert: needsFrame.
- 	numArgs > 2 ifTrue:
- 		[self MoveCq: numArgs R: SendNumArgsReg].
- 	self MoveCw: selector R: ClassReg.
- 	self CallSend: (superSendTrampolines at: (numArgs min: NumSendTrampolines - 1)).
- 	optStatus isReceiverResultRegLive: false.
- 	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSend:numArgs: (in category 'bytecode generators') -----
  genSend: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genSendAbsentDynamicSuper: selector numArgs: numArgs
  	"OK, we could do better and avoid spilling ReceiverResultReg if we refactored
  	 marshallImplicitReceiverSendArguments: to take a flag saying whether the
  	 receiver was in ReceiverResultReg (absent receiver send) or on the stack
  	 (absent dynamic super send) and in the latter case loading ReceiverResultReg
  	 from the stack after marshalling.  But this is a rare bytecode so for the moment
  	 don't bother."
  	self ssAllocateCallReg: ReceiverResultReg.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!
- 	^self genMarshalledSendDynamicSuper: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
  genSendAbsentImplicit: selector numArgs: numArgs
  	"Get the implicit receiver and marshall arguments, shuffling the
  	 stack to push the implicit receiver if necessary. Then send."
  	<inline: false>
  	| result |
  	"This must not be PC-mapped"
  	result := self genGetImplicitReceiverFor: selector forPush: false.
  	result ~= 0 ifTrue:
  		[^result].
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentOuter:numArgs:depth: (in category 'bytecode generators') -----
  genSendAbsentOuter: selector numArgs: numArgs depth: depth
  	"OK, we could do better and avoid spilling ReceiverResultReg if we refactored
  	 marshallAbsentReceiverSendArguments: to take a flag saying whether the
  	 receiver was in ReceiverResultReg (absent receiver send) or on the stack
  	 (absent dynamic super send) and in the latter case loading ReceiverResultReg
  	 from the stack after marshalling.  But this is a rare bytecode so for the moment
  	 don't bother."
  	optStatus isReceiverResultRegLive: false.
  	self ssAllocateCallReg: SendNumArgsReg.
  	self MoveCq: depth R: SendNumArgsReg.
  	self CallRT: ceEnclosingObjectTrampoline.
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentSelf:numArgs: (in category 'bytecode generators') -----
  genSendAbsentSelf: selector numArgs: numArgs
  	"OK, we could do better and avoid spilling ReceiverResultReg if we refactored
  	 marshallAbsentReceiverSendArguments: to take a flag saying whether the
  	 receiver was in ReceiverResultReg (absent receiver send) or on the stack
  	 (absent dynamic super send) and in the latter case loading ReceiverResultReg
  	 from the stack after marshalling.  But this is a rare bytecode so for the moment
  	 don't bother."
  	self ssAllocateCallReg: ReceiverResultReg.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	self marshallAbsentReceiverSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: selfSendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendDynamicSuper:numArgs: (in category 'bytecode generators') -----
  genSendDynamicSuper: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!
- 	^self genMarshalledSendDynamicSuper: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendSuper:numArgs: (in category 'bytecode generators') -----
  genSendSuper: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: superSendTrampolines!
- 	^self genMarshalledSendSuper: selector numArgs: numArgs!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
  	 jumpNotSmallInts jumpContinue annotateInst instToAnnotate |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #instToAnnotate type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
  			["Must enter any annotatedConstants into the map"
  			 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  			 self annotateBytecodeIfAnnotated: self ssTop.
  			 "Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[self ssFlushTo: simStackPtr - 2.
  			 (self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self AddCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
  								ifFalse:
  									[self SubR: Arg0Reg R: ReceiverResultReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self SubCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
  							 self SubR: Arg0Reg R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
  		[AndRR] -> [argIsInt
  						ifTrue: [instToAnnotate := self AndCq: argInt R: ReceiverResultReg]
  						ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
  						ifTrue: [instToAnnotate := self OrCq: argInt R: ReceiverResultReg]
  						ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[annotateInst ifTrue: [self annotateBytecode: instToAnnotate].
  		 self MoveCq: argInt R: Arg0Reg].
  	self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
+ 		numArgs: 1
+ 		sendTable: ordinarySendTrampolines.
- 		numArgs: 1.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
  		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  		 self annotateBytecodeIfAnnotated: self ssTop.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
+ 		numArgs: 1
+ 		sendTable: ordinarySendTrampolines.!
- 		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
- 		sendTrampolines
  			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
- 	sendTrampolines
  		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).
  	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.
- 	firstSend := sendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!



More information about the Vm-dev mailing list