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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 5 00:46:16 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1160
Author: rmacnak
Time: 4 April 2015, 4:42:13.581 pm
UUID: 26e10c05-71b4-46ee-b067-f15df51e39dd
Ancestors: VMMaker.oscog-eem.1159

Implement outer sends as clean sends just like implicit receiver sends. Add ObjectRepresentation>>illegalClassTag and use it for initializing and unlinking implicit and outer sends.

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

Item was added:
+ ----- Method: CoInterpreter>>ceOuterSend:receiver: (in category 'trampolines') -----
+ ceOuterSend: cacheAddress receiver: methodReceiver
+ 	"An outer send cache missed."
+ 	| nsSendCache methodMixin numArgs selector depth enclosingObject cogMethod eoClassTag 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.
+ 	depth := nsSendCache depth.
+ 	methodMixin := self mMethodClass.
+ 
+ 	enclosingObject := self
+ 		enclosingObjectAt: depth
+ 		withObject: methodReceiver
+ 		withMixin: methodMixin.
+ 
+ 	self assert: (self stackValue: numArgs + 1 "ret val") = methodReceiver.
+ 	self stackValue: numArgs + 1 "ret val " put: enclosingObject.
+ 	"Replace the methodReceiver on the stack with the enclosingObject. 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.
+ 	eoClassTag := objectMemory fetchClassTagOf: enclosingObject.
+ 	argumentCount := numArgs.
+ 
+ 	(self lookupInMethodCacheSel: selector classTag: eoClassTag)
+ 		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: eoClassTag) ifTrue:
+ 				[self error: 'Implicit receiver lookup should have followed fowarded objects'].
+ 			messageSelector := selector.
+ 			(errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: eoClassTag)) ~= 0
+ 				ifTrue: [[self handleMNU: errSelIdx InMachineCodeTo: enclosingObject classForMessage: (objectMemory classForClassTag: eoClassTag).
+ 						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: enclosingObject
+ 						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 added:
+ ----- Method: CogObjectRepresentation>>illegalClassTag (in category 'in-line cacheing') -----
+ illegalClassTag
+ 	"Answer a class tag that will fail for every object."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>illegalClassTag (in category 'in-line cacheing') -----
+ illegalClassTag
+ 	<inline: true>
+ 	^2!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>illegalClassTag (in category 'in-line cacheing') -----
+ illegalClassTag
+ 	<inline: true>
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>illegalClassTag (in category 'in-line cacheing') -----
+ illegalClassTag
+ 	<inline: true>
+ 	^0!

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 outerSendTrampolines'
- 	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'
  	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' 'nsSendCacheSurrogateClass'
  		'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' 'outerSendTrampolines'
- 			'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'implicitReceiverSendTrampolines'
  			'ceEnclosingObjectTrampoline' '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:'#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
  					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: #outerSendTrampolines
+ 			declareC: 'sqInt outerSendTrampolines[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>>generateNewspeakSendTrampolines (in category 'initialization') -----
  generateNewspeakSendTrampolines
+ 	"Self send, dynamic super send, implicit receiver send, and outer send"
- 	"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)).
+ 
+ 	0 to: NumSendTrampolines - 2 do:
+ 		[:numArgs|
+ 		outerSendTrampolines
+ 			at: numArgs
+ 			put: (self 
+ 				genNSSendTrampolineFor: #ceOuterSend:receiver:
+ 				numArgs: numArgs
+ 				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))].
+ 	outerSendTrampolines
+ 		at: NumSendTrampolines - 1
+ 		put: (self 
+ 			genNSSendTrampolineFor: #ceOuterSend:receiver:
+ 			numArgs: self numRegArgs + 1
+ 			called: (self trampolineName: 'ceOuterSend' numArgs: -1)).
+ 
+ !
- 			called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: -1)).!

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 |
  
  	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[|  nsSendCache |
  		 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 		 nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "send is linked"
- 		 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 > 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 removed:
- ----- 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 added:
+ ----- Method: Cogit>>initializeNSSendCache:selector:numArgs:depth: (in category 'newspeak support') -----
+ initializeNSSendCache: cacheAddress selector: selector numArgs: numArgs depth: depth
+ 	| nsSendCache |
+ 	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
+ 	nsSendCache selector: selector.
+ 	nsSendCache numArgs: numArgs.
+ 	nsSendCache depth: depth.
+ 	nsSendCache classTag: objectRepresentation illegalClassTag.
+ !

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := 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:
  		[| nsSendCache 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: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 					[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 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]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: delta
  	<var: #mcpc type: #'char *'>
  	| entryPoint offset sendTable targetMethod unlinkedRoutine |
  	<var: #sendTable type: #'sqInt *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
+ 						[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 						[nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
  			^0]].
  
  	annotation = IsSendCall ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [: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>>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).
+ 		outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
- 		implicitReceiverSendTrampolines := 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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 			nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue:
- 			nsSendCache classTag ~= 0 ifTrue:
  				[(objectMemory isForwardedClassIndex: nsSendCache classTag) ifTrue: [
+ 					nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 					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 := 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]]]].
  
  	^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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(targetMethod cmType = CMFree or: [nsSendCache selector = theSelector]) ifTrue:
+ 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 					[nsSendCache classTag: 0; enclosingObject: 0; target: 0]].
  			^0 "keep scanning"]].
  
  	annotation = IsSendCall 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]]]].
  
  	^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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
+ 			nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "Send is linked"
+ 				[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0].
- 			nsSendCache classTag ~= 0 ifTrue: "Send is linked"
- 				[nsSendCache classTag: 0; enclosingObject: 0; target: 0].
  			^0 "keep scanning"]].
  
  	annotation = IsSendCall 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]]].
  
  	^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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache selector = theSelector ifTrue:
+ 				[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0].
- 				[nsSendCache classTag: 0; enclosingObject: 0; target: 0].
  			^0 "keep scanning"]].
  
  	annotation = IsSendCall 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]]]].
  
  	^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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := entryPoint - cmNoCheckEntryOffset.
  				targetMethod = theCogMethod ifTrue:
+ 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 					[nsSendCache classTag: 0.
- 					nsSendCache enclosingObject: 0.
- 					nsSendCache target: 0]].
  			^0 "keep scanning"]].
  
  	annotation = IsSendCall 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]]]].
  
  	^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 |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache nsTargetMethod |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue: "It's a linked send."
  				[nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				nsTargetMethod cmType = CMFree ifTrue:
+ 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
- 					[nsSendCache classTag: 0.
- 					nsSendCache enclosingObject: 0.
- 					nsSendCache target: 0]].
  			^0 "keep scanning"]].
  
  	annotation = IsSendCall 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 changed:
  VMStructType subclass: #NSSendCache
+ 	instanceVariableNames: 'classTag enclosingObject target selector numArgs depth'
- 	instanceVariableNames: 'selector numArgs classTag enclosingObject target'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!

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

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

Item was changed:
  ----- Method: NSSendCacheSurrogate32 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^24!
- 	^20!

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

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

Item was added:
+ ----- Method: NSSendCacheSurrogate32>>depth (in category 'accessing') -----
+ depth
+ 	^memory unsignedLongAt: address + 21!

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

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

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

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

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

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

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

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

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

Item was changed:
  ----- Method: NSSendCacheSurrogate64 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^48!
- 	^40!

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

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

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

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

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

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

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

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

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

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

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

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

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode)
  		(1  79   79 genPushConstantOneBytecode)
  
  		(1   80 101 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
  		(1 176 183 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  		(2 226 226 genExtPushReceiverVariableBytecode)
  		(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 hasIRC)
- 		(3 254 254 genExtSendAbsentOuterBytecode isMapped)
  
  		(3 255 255	unknownBytecode))!

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
  genSendAbsentImplicit: selector numArgs: numArgs
- 	| nsSendCache |
  	<inline: false>
+ 	^self
+ 		genSendAbsentImplicitOrOuter: selector
+ 		numArgs: numArgs
+ 		depth: 255 "Unused"
+ 		sendTable: implicitReceiverSendTrampolines!
- 	(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."
- 	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!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
+ 	| nsSendCache |
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 
+ 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
+ 	indexOfIRC := indexOfIRC + 1.
+ 	self assert: (objectMemory isInOldSpace: nsSendCache).
+ 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
+ 
+ 	self 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."
+ 	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	self PushR: ReceiverResultReg.
+ 	^0!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:numInitialNils:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode 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 hasIRC)
- 		(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: [70]
- 							ifTrue: [66]
  							ifFalse: [52]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
- genSendAbsentImplicit: selector numArgs: numArgs
- 	| nsSendCache |
- 	<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."
- 	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!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
+ 	<var: #sendTable type: #'sqInt *'>
+ 	| nsSendCache |
+ 	(objectMemory isYoung: selector) ifTrue:
+ 		[hasYoungReferent := true].
+ 
+ 	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
+ 	indexOfIRC := indexOfIRC + 1.
+ 	self assert: (objectMemory isInOldSpace: nsSendCache).
+ 	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
+ 
+ 	self ssAllocateCallReg: 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."
+ 	self marshallAbsentReceiverSendArguments: numArgs.
+ 
+ 	"Load the cache last so it is a fixed distance from the call."
+ 	self MoveCw: nsSendCache R: SendNumArgsReg.
+ 	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
+ 
+ 	optStatus isReceiverResultRegLive: false.
+ 	^self ssPushRegister: ReceiverResultReg!

Item was removed:
- ----- 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!

Item was changed:
  ----- 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)).
+ 
+ 	0 to: NumSendTrampolines - 2 do:
+ 		[:numArgs|
+ 		outerSendTrampolines
+ 			at: numArgs
+ 			put: (self 
+ 				genNSSendTrampolineFor: #ceOuterSend:receiver:
+ 				numArgs: numArgs
+ 				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))].
+ 	outerSendTrampolines
+ 		at: NumSendTrampolines - 1
+ 		put: (self 
+ 			genNSSendTrampolineFor: #ceOuterSend:receiver:
+ 			numArgs: self numRegArgs + 1
+ 			called: (self trampolineName: 'ceOuterSend' numArgs: -1)).!
- 			called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: -1)).!



More information about the Vm-dev mailing list