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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 12 19:22:41 UTC 2018


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

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

Name: VMMaker.oscog-eem.2315
Author: eem
Time: 12 January 2018, 11:22:17.267383 am
UUID: 7bb299f2-2888-4047-b9ea-826c6a27d890
Ancestors: VMMaker.oscog-eem.2314

Double-back on the rash statement that there was a bad bug in ceSend:above:to:numArgs: which was written to accept an association, not a class.  This was by design.  generalize the JIT support for directed super sends so that it accepts both the
	pushLiteral: foo; directedSuperSend: bar numArgs: baz, and
	pushLiteralVariable: foo; directedSuperSend: bar numArgs: baz
forms.  Introduce aother directed send trampoline table for directedSuperBindingSends.  Implement ceSend:aboveClassBinding:to:numArgs: using ceSend:above:to:numArgs:.

Simplify, deleting genPushLiteralVariableGivenDirectedSuper: et al, and simply having genPushLiteralIndex: peek for a directed super send if the bytecode set includes it.  Add the directedSendUsesBinding variable, set only by genPushLiteralIndex: and consumed by genSendDirectedSuper:numArgs:, to distinguish between the two forms.

Keep the unused printPCMapPairsFor:, but mark it as doNotGenerate.
Implement targetMethodAndSendTableFor:annotation:into: in terms of offsetAndSendTableFor:annotation:into:.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSend:above:to:numArgs: (in category 'trampolines') -----
  ceSend: selector above: methodClass to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
+ 	methodClass is the class above which to start the lookup.
- 	startAssociation is an association whose value is the class above which to start the lookup.
  
  	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: #BytecodeSetHasDirectedSuperSend>
  	| classTag classObj errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory followMaybeForwarded: methodClass)).
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[self deny: (objectMemory isForwardedClassTag: classTag).
  			 (objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					above: methodClass
  					to: rcvr
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 classObj := objectMemory classForClassTag: classTag.
  			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: cogit noCheckEntryOffset
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: classObj.
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 We must not link to an Open PIC since they perform normal sends."
  	(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 noCheckEntryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was added:
+ ----- Method: CoInterpreter>>ceSend:aboveClassBinding:to:numArgs: (in category 'trampolines') -----
+ ceSend: selector aboveClassBinding: methodClassBinding to: rcvr numArgs: numArgs
+ 	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
+ 					receiver
+ 					args
+ 		head sp ->	sender return pc
+ 	methodClassBinding is an association whose value is the class above which to start the lookup."
+ 	<api>
+ 	<option: #BytecodeSetHasDirectedSuperSend>
+ 	self ceSend: selector
+ 		above: (objectMemory followMaybeForwarded: methodClassBinding)
+ 		to: rcvr
+ 		numArgs: numArgs!

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 enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointer
 s ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperBindingSend IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
- 	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 enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointer
 s ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/25/2017 17:53' 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.
  
  	SistaCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  	RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
  	to registers. It is inended to serve as the superclass to SistaCogit once it is working.
  
  	SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
  	SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
  	will replace SistaCogit.
  
  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.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
  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 eventually the 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:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'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 precede 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: #ceGetFP
  			declareC: 'usqIntptr_t (*ceGetFP)(void)';
  		var: #ceGetSP
  			declareC: 'usqIntptr_t (*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)(usqIntptr_t from, usqIntptr_t to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'usqIntptr_t (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	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'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					fullBlockNoContextSwitchEntry fullBlockEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
+ 			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'.
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[aCCodeGenerator
+ 			var: #directedSuperSendTrampolines
+ 				declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
+ 			var: #directedSuperBindingSendTrampolines
+ 				declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]'].
+ 	NewspeakVM ifTrue:
+ 		[aCCodeGenerator
+ 			var: #selfSendTrampolines
+ 				declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
+ 			var: #dynamicSuperSendTrampolines
+ 				declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
+ 			var: #implicitReceiverSendTrampolines
+ 				declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
+ 			var: #outerSendTrampolines
+ 				declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]'].
+ 	aCCodeGenerator
- 			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
- 		var: #directedSuperSendTrampolines
- 			declareC: 'sqInt directedSuperSendTrampolines[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 usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]';
  		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: #'usqIntptr_t';
  		declareVar: #debugPrimCallStackOffset type: #'usqIntptr_t'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit class>>initializeAnnotationConstants (in category 'class initialization') -----
  initializeAnnotationConstants
  	"These form the method map for a cog method.  The map defines which addresses
  	 in a machine code method are ones with important functions, such as being a send
  	 site or being a reference to a heap object.  Each annotated instruction has a byte
  	 in the map, and each byte in the map has two parts.  In the least signficant bits are
  	 a distance in codeGranularity units from the start of the method or the previous
  	 map entry, except for the IsAnnotationExtension type.  In the most signficant bits
  	 are the type of annotation at the point reached.  A null byte ends the map.  The
  	 first mapped location is a distance from the cmNoCheckEntryOffset.
  
  	 The map occurs at the end of a method (*), in reverse, so that its start is found
  	 by adding the method's block size.  If the distance between two mapped
  	 instructions will not fit in the displacement field then one or more displacement
  	 entries are placed in the map to bridge the gap.  There is a * 32 displacement
  	 units type for spanning large gaps.  The displacements are in codeGranularity
  	 units so that processors like e.g. ARM, with 4-byte instructions, do not have overly
  	 large maps.  In [practice maps are very compact, but they should be as quick to
  	 navigate as possible, and hence be as compact as possible.
  
  	 There is only one kind of call annotation that serves for all calls from machine
  	 code. There are several kinds of call, sends, super sends, calls of the generated
  	 run-time, and direct calls of primitive functions in the interpreter.  These need
  	 different treatment at different times.  For example, when the send cache is
  	 flushed or the method zone is shrunk some sends must be unlinked and some
  	 sends must be relocated.  But to be able to parse bytecoded methods and match
  	 their pcs with corresponding machine code pcs the map needs to differentiate
  	 between sends and run-time calls. 
  
  	 Sends can be distinguished from run-time or direct primitive calls based on address;
  	 only sends have their target between methodZoneBase and methodZone freeStart.
  	 We used to distinguish normal sends from super sends based on alignment of
  	 entry-point, because normal sends link to the checked entry-point, whereas super sends
  	 link to the unchecked entry-point, and both entry points have different alignments.
  	 But now we use the IsAnnotationExtension to label sends other than normal sends.
  	 For these ``exotic'' sends there is both an IsAnnotationExtension annotation and an
  	 IsSendCall annotation.
  
  	 While run-time calls can be distinguished from direct primitive calls on the basis
  	 of address there is no need to do so.  They are merely calls to locations that
  	 don't move during method zone compaction.
  
  	 Absolute PC references are used for method references and counter references.
  	 These are references from within a particular method to absolute pcs in that same
  	 method that must be relocated when the method moves."
  	"self initializeAnnotationConstants"
  
  	AnnotationShift := 5.
  	IsDisplacementX2N := 0.	"N.B. A 0 byte ends the map"
  	IsAnnotationExtension := 1.	"Used to extend IsSendCall with different codes for exotic send types."
  	IsObjectReference := 2.
  	IsAbsPCReference := 3.
  	IsRelativeCall := 4.
  	HasBytecodePC := 5.
  	IsNSSendCall := NewspeakVM ifTrue: [6].
  	IsSendCall := 7.
  	"These are formed by combining IsSendCall and IsAnnotationExtension annotations."
  	IsSuperSend := 8.
+ 	IsDirectedSuperSend := BytecodeSetHasDirectedSuperSend ifTrue: [9].
+ 	IsDirectedSuperBindingSend := BytecodeSetHasDirectedSuperSend ifTrue: [10].
+ 	IsNSSelfSend := NewspeakVM ifTrue: [11].
+ 	IsNSDynamicSuperSend := NewspeakVM ifTrue: [12].
+ 	IsNSImplicitReceiverSend := NewspeakVM ifTrue: [13].
- 	IsDirectedSuperSend := 9.
- 	IsNSSelfSend := NewspeakVM ifTrue: [10].
- 	IsNSDynamicSuperSend := NewspeakVM ifTrue: [11].
- 	IsNSImplicitReceiverSend := NewspeakVM ifTrue: [12].
  
  	DisplacementMask := (1 << AnnotationShift) - 1.
  	DisplacementX2N := IsDisplacementX2N << AnnotationShift.
  	FirstAnnotation := IsObjectReference << AnnotationShift.
  	MaxX2NDisplacement := DisplacementMask << AnnotationShift.
  
  	MapEnd := 0.
  
  	AnnotationConstantNames := #(	IsDisplacementX2N
  										IsAnnotationExtension
  										IsObjectReference
  										IsAbsPCReference
  										IsRelativeCall
  										HasBytecodePC
  										IsNSSendCall
  										IsSendCall
  										IsSuperSend
  										IsDirectedSuperSend
+ 										IsDirectedSuperBindingSend
  										IsNSSelfSend
  										IsNSDynamicSuperSend
  										IsNSImplicitReceiverSend).
  	AnnotationsWithBytecodePCs := #(HasBytecodePC
  										IsNSSendCall
  										IsSendCall
  										IsSuperSend
  										IsDirectedSuperSend
+ 										IsDirectedSuperBindingSend
  										IsNSSelfSend
  										IsNSDynamicSuperSend
  										IsNSImplicitReceiverSend),
  										{'IsRelativeCall:\HasBytecodePC' withCRs}!

Item was changed:
  ----- Method: Cogit class>>initializeNumTrampolines (in category 'class initialization') -----
  initializeNumTrampolines
  	NumTrampolines := self numTrampolines
  						+ self objectRepresentationClass numTrampolines
+ 						+ (NewspeakVM ifTrue: [NumSendTrampolines * 4 + 2] ifFalse: [0])
+ 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [NumSendTrampolines * 2] ifFalse: [0])!
- 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
- 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!

Item was changed:
  ----- Method: Cogit>>annotationIsForUncheckedEntryPoint: (in category 'in-line cacheing') -----
  annotationIsForUncheckedEntryPoint: annotation
  	<inline: true>
  	^annotation = IsSuperSend
+ 	  or: [BytecodeSetHasDirectedSuperSend
+ 		  and: [annotation
+ 					between: IsDirectedSuperSend
+ 					and: IsDirectedSuperBindingSend]]!
- 	  or: [BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]]!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	| cPIC endAddress |
  	<var: 'cPIC' type: #'CogMethod *'>
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: MaxCPICCases * 9 bytecodes: 0.
  	methodLabel address: methodZoneBase; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
  	cPIC := (self cCoerceSimple: methodZoneBase to: #'CogMethod *').
  	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
  	endAddress := self outputInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	self assert: methodZoneBase + closedPICSize = endAddress.
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICEndOfCodeOffset := cPICEndOfCodeLabel address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
  	cPICEndSize := closedPICSize - (MaxCPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize.
  	self assert: picInterpretAbort address = (methodLabel address + self picInterpretAbortOffset).
  	self assert: (self expectedClosedPICPrototype: cPIC) = 0.
  	
  	"tpr this is a little tiresome but after any assert checking we need to 0 out the case0 objRef rather than leaving 16r5EAF00D lying around"
  
  	backEnd storeLiteral: 0 beforeFollowingAddress: endCPICCase0 address - backEnd jumpLongByteSize.
  	
+ 	"update the methodZoneBase so we keep the prototype around for later use"
- 	"update the methodZoneBase so we keep the prototype aruond for later use"
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	cPICPrototype := cPIC.
  	"self cCode: ''
  		inSmalltalk:
  			[self disassembleFrom: cPIC + (self sizeof: CogMethod) to: cPIC + closedPICSize - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: (self trampolineArgConstant: false)
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	NewspeakVM ifTrue:
  		[self generateNewspeakSendTrampolines].
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[0 to: NumSendTrampolines - 1 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genTrampolineFor: #ceSend:above:to:numArgs:
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
+ 						  arg: (self numArgsOrSendNumArgsReg: numArgs)).
+ 			directedSuperBindingSendTrampolines
+ 				at: numArgs
+ 				put: (self genTrampolineFor: #ceSend:aboveClassBinding:to:numArgs:
+ 						  called: (self trampolineName: 'ceDirectedSuperBindingSend' numArgs: numArgs)
+ 						  arg: ClassReg
+ 						  arg: TempReg
+ 						  arg: ReceiverResultReg
  						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: (self trampolineArgConstant: true)
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 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
  	 annotation.  c.f. annotationForSendTable:"
  	<inline: true>
  	| offset sendTable |
  	<var: #sendTable type: #'sqInt *'>
  	annotation = IsSendCall ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := ordinarySendTrampolines] ifFalse:
  	[(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[offset := cmNoCheckEntryOffset.
  		 sendTable := directedSuperSendTrampolines] ifFalse:
+ 	[(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperBindingSend]) ifTrue:
+ 		[offset := cmNoCheckEntryOffset.
+ 		 sendTable := directedSuperBindingSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSDynamicSuperSend]) ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := dynamicSuperSendTrampolines] ifFalse:
  	[self assert: annotation = IsSuperSend.
  	 offset := cmNoCheckEntryOffset.
+ 	 sendTable := superSendTrampolines]]]]].
- 	 sendTable := superSendTrampolines]]]].
  
  	binaryBlock
  		value: offset
  		value: sendTable!

Item was changed:
  ----- Method: Cogit>>printPCMapPairsFor: (in category 'method map') -----
  printPCMapPairsFor: cogMethod
+ 	<doNotGenerate>
+ 	"<api>
- 	<api>
  	<var: 'cogMethod' type: #'CogMethod *'>
+ 	<var: 'mapByte' type: #'unsigned char'>"
- 	<var: 'mapByte' type: #'unsigned char'>
  	| mcpc map mapByte annotation value |
  	mcpc := self firstMappedPCFor: cogMethod.
  	map := self mapStartFor: cogMethod.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
  		[annotation := mapByte >> AnnotationShift.
  		 annotation = IsAnnotationExtension
  			ifTrue:
  				[value := (mapByte bitAnd: DisplacementMask) + IsSendCall]
  			ifFalse:
  				[value := annotation.
  				 mcpc := mcpc + (backEnd codeGranularity
  									* (annotation = IsDisplacementX2N
  										ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  										ifFalse: [mapByte bitAnd: DisplacementMask]))].
  		 coInterpreter
  			printHexnp: map;
  		 	print: ': '.
  		 self
  			cCode: [self print: '%02x' f: mapByte]
  			inSmalltalk:
  				[mapByte < 16 ifTrue:
  					[coInterpreter putchar: $0].
  				 coInterpreter printHexnp: mapByte].
  		 coInterpreter
  		 	printChar: $ ;
  			printNum: annotation;
  			print: ' ('.
+ 		 (NewspeakVM
+ 		  and: [value = IsNSSendCall
+ 			     or: [value between: IsNSSendCall and: IsNSImplicitReceiverSend]]) ifTrue:
+ 			[value
+ 				caseOf: {
+ 					[IsNSSendCall]				->	[coInterpreter print: 'NSSendCall'].
+ 					[IsNSSelfSend]				->	[coInterpreter print: 'NSSelfSend'].
+ 					[IsNSDynamicSuperSend]	->	[coInterpreter print: 'NSDynamicSuperSend'].
+ 					[IsNSImplicitReceiverSend]	->	[coInterpreter print: 'NSImplicitReceiverSend'] }] ifFalse:
+ 		 [(BytecodeSetHasDirectedSuperSend
+ 		    and: [value between: IsDirectedSuperSend and: IsDirectedSuperBindingSend]) ifTrue:
+ 			[value
+ 				caseOf: {
+ 					[IsDirectedSuperSend]			->	[coInterpreter print: 'DirectedSuperSend'].
+ 					[IsDirectedSuperBindingSend]	->	[coInterpreter print: 'DirectedSuperBindingSend'] }] ifFalse:
+ 		 [value
+ 			caseOf: {
+ 				[IsDisplacementX2N]		->	[coInterpreter print: 'DisplacementX2N'].
+ 				[IsAnnotationExtension]	->	[coInterpreter print: 'AnnotationExtension'].
+ 				[IsObjectReference]			->	[coInterpreter print: 'ObjectReference'].
+ 				[IsAbsPCReference]			->	[coInterpreter print: 'AbsPCReference'].
+ 				[HasBytecodePC]			->	[coInterpreter print: 'HasBytecodePC'].
+ 				[IsRelativeCall]				->	[coInterpreter print: 'RelativeCall'].
+ 				[IsSendCall]				->	[coInterpreter print: 'SendCall'].
+ 				[IsSuperSend]				->	[coInterpreter print: 'SuperSend'] }
+ 			otherwise: [coInterpreter print: '??? '; printHexnp: value]]].
- 		 NewspeakVM
- 			ifTrue:
- 				[value
- 					caseOf: {
- 						[IsDisplacementX2N]		->	[coInterpreter print: 'IsDisplacementX2N'].
- 						[IsAnnotationExtension]		->	[coInterpreter print: 'IsAnnotationExtension'].
- 						[IsObjectReference]		->	[coInterpreter print: 'IsObjectReference'].
- 						[IsAbsPCReference]		->	[coInterpreter print: 'IsAbsPCReference'].
- 						[HasBytecodePC]			->	[coInterpreter print: 'HasBytecodePC'].
- 						[IsRelativeCall]				->	[coInterpreter print: 'IsRelativeCall'].
- 						[IsNSSendCall]				->	[coInterpreter print: 'IsNSSendCall'].
- 						[IsSendCall]					->	[coInterpreter print: 'IsSendCall'].
- 						[IsSuperSend]				->	[coInterpreter print: 'IsSuperSend'].
- 						[IsDirectedSuperSend]		->	[coInterpreter print: 'IsDirectedSuperSend'].
- 						[IsNSSelfSend]				->	[coInterpreter print: 'IsNSSelfSend'].
- 						[IsNSDynamicSuperSend]	->	[coInterpreter print: 'IsNSDynamicSuperSend'].
- 						[IsNSImplicitReceiverSend]	->	[coInterpreter print: 'IsNSImplicitReceiverSend'] }
- 					otherwise: [coInterpreter print: '??? '; printHexnp: value]]
- 			ifFalse:
- 				[value
- 					caseOf: {
- 						[IsDisplacementX2N]		->	[coInterpreter print: 'IsDisplacementX2N'].
- 						[IsAnnotationExtension]		->	[coInterpreter print: 'IsAnnotationExtension'].
- 						[IsObjectReference]		->	[coInterpreter print: 'IsObjectReference'].
- 						[IsAbsPCReference]		->	[coInterpreter print: 'IsAbsPCReference'].
- 						[HasBytecodePC]			->	[coInterpreter print: 'HasBytecodePC'].
- 						[IsRelativeCall]				->	[coInterpreter print: 'IsRelativeCall'].
- 						[IsSendCall]					->	[coInterpreter print: 'IsSendCall'].
- 						[IsSuperSend]				->	[coInterpreter print: 'IsSuperSend'].
- 						[IsDirectedSuperSend]		->	[coInterpreter print: 'IsDirectedSuperSend'] }
- 					otherwise: [coInterpreter print: '??? '; printHexnp: value]].
  		 coInterpreter
  			print: ') ';
  			printHexnp: (mapByte bitAnd: DisplacementMask);
  			printChar: $ ;
  			putchar: $@;
  		 printHex: mcpc;
  		 cr;
  		 flush.
  		 map := map - 1]!

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 := self class methodZoneClass new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
  					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  					ifFalse: [0].
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	backEnd := CogCompilerClass for: self.
  	methodLabel := CogCompilerClass for: self.
  	(literalsManager := backEnd class literalsManagerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
+ 		 directedSuperBindingSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
+ 		 directedSendUsesBinding := false].
- 		[directedSuperSendTrampolines := 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)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	extA := numExtB := extB := 0.
  
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
  	debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].
  	debugBytecodePointers := self class initializationOptions at: #debugBytecodePointers ifAbsent: [Set new].
  	self class initializationOptions at: #breakPC ifPresent: [:pc| breakPC := pc]!

Item was changed:
  ----- Method: Cogit>>targetMethodAndSendTableFor:annotation:into: (in category 'in-line cacheing') -----
  targetMethodAndSendTableFor: entryPoint annotation: annotation 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 offsetAndSendTableFor: entryPoint
+ 		annotation: annotation
+ 		into: [:offset :sendTable| | targetMethod |
+ 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 			binaryBlock
+ 				value: targetMethod
+ 				value: sendTable]!
- 	annotation = IsSendCall ifTrue:
- 		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
- 		 sendTable := ordinarySendTrampolines] ifFalse:
- 	[(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]) ifTrue:
- 		[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
- 		 sendTable := directedSuperSendTrampolines] ifFalse:
- 	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
- 		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
- 		 sendTable := selfSendTrampolines] ifFalse:
- 	[(NewspeakVM and: [annotation = IsNSDynamicSuperSend]) ifTrue:
- 		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
- 		 sendTable := dynamicSuperSendTrampolines] ifFalse:
- 	[self assert: annotation = IsSuperSend.
- 	 targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
- 	 sendTable := superSendTrampolines]]]].
- 
- 	binaryBlock
- 		value: targetMethod
- 		value: sendTable!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>annotationForSendTable: (in category 'bytecode generator support') -----
  annotationForSendTable: sendTable
  	"c.f. offsetAndSendTableFor:annotation:into:"
  	<inline: true>
  	<var: #sendTable type: #'sqInt *'>
+ 	sendTable == ordinarySendTrampolines ifTrue:
+ 		[^IsSendCall].
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[sendTable == directedSuperSendTrampolines ifTrue:
+ 			[^IsDirectedSuperSend].
+ 		 sendTable == directedSuperBindingSendTrampolines ifTrue:
+ 			[^IsDirectedSuperBindingSend]].
+ 	NewspeakVM ifTrue:
+ 		[sendTable == implicitReceiverSendTrampolines ifTrue:
+ 			[self error: 'Unexpected implicit receiver send using dirty send machinery'].
+ 		 sendTable == outerSendTrampolines ifTrue:
+ 			[self error: 'Unexpected outer send using dirty send machinery'].
+ 		sendTable == selfSendTrampolines ifTrue:
+ 			[^IsNSSelfSend].
+ 		sendTable == dynamicSuperSendTrampolines ifTrue:
+ 			[^IsNSDynamicSuperSend]].
+ 	self assert: sendTable == superSendTrampolines.
+ 	^IsSuperSend!
- 	(NewspeakVM and: [sendTable == implicitReceiverSendTrampolines]) ifTrue:
- 		[self error: 'Unexpected implicit receiver send using dirty send machinery'].
- 	(NewspeakVM and: [sendTable == outerSendTrampolines]) ifTrue:
- 		[self error: 'Unexpected outer send using dirty send machinery'].
- 	(NewspeakVM and: [sendTable == selfSendTrampolines]) ifTrue:
- 		[^IsNSSelfSend].
- 	(NewspeakVM and: [sendTable == dynamicSuperSendTrampolines]) ifTrue:
- 		[^IsNSDynamicSuperSend].
- 	(BytecodeSetHasDirectedSuperSend and: [sendTable == directedSuperSendTrampolines]) ifTrue:
- 		[^IsDirectedSuperSend].
- 	sendTable == superSendTrampolines ifTrue:
- 		[^IsSuperSend].
- 	self assert: sendTable == ordinarySendTrampolines.
- 	^IsSendCall!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genExtPushLitVarDirSupBytecode (in category 'bytecode generators') -----
- genExtPushLitVarDirSupBytecode
- 	"227		11100011	i i i i i i i i	Push Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	| index |
- 	index := byte1 + (extA << 8).
- 	extA := 0.
- 	^self genPushLiteralVariableGivenDirectedSuper: index!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushLitVarDirSup16CasesBytecode (in category 'bytecode generators') -----
- genPushLitVarDirSup16CasesBytecode
- 	"e.g. SistaV1: 16-31		0001 iiii			Push Literal Variable #iiii"
- 	^self genPushLiteralVariableGivenDirectedSuper: (byte0 bitAnd: 15)!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushLitVarDirSupBytecode (in category 'bytecode generators') -----
- genPushLitVarDirSupBytecode
- 	^self genPushLiteralVariableGivenDirectedSuper: (byte0 bitAnd: 31)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralIndex: (in category 'bytecode generator support') -----
  genPushLiteralIndex: literalIndex "<SmallInteger>"
  	<inline: false>
  	| literal |
  	literal := self getLiteral: literalIndex.
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[self nextDescriptorExtensionsAndNextPCInto:
+ 			[:descriptor :exta :extb :followingPC|
+ 			(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
+ 				[tempOop := literal.
+ 				 ^0]]].
  	^self genPushLiteral: literal!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralVariable: (in category 'bytecode generator support') -----
  genPushLiteralVariable: literalIndex
  	<inline: false>
  	| association |
  	association := self getLiteral: literalIndex.
+ 	"If followed by a directed super send bytecode, avoid generating any code yet.
+ 	 The association will be passed to the directed send trampoline in a register
+ 	 and fully dereferenced only when first linked.  It will be ignored in later sends."
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[self deny: directedSendUsesBinding.
+ 		 self nextDescriptorExtensionsAndNextPCInto:
+ 			[:descriptor :exta :extb :followingPC|
+ 			(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
+ 				[tempOop := association.
+ 				 directedSendUsesBinding := true.
+ 				 ^0]]].
  	"N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods."
  	self genMoveConstant: association R: ClassReg.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: ClassReg
  		scratchReg: TempReg.
  	objectRepresentation
  		genLoadSlot: ValueIndex
  		sourceReg: ClassReg
  		destReg: TempReg.
  	self PushR: TempReg.
  	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushLiteralVariableGivenDirectedSuper: (in category 'bytecode generator support') -----
- genPushLiteralVariableGivenDirectedSuper: literalIndex
- 	"This is a version of genPushLiteralVariable: that looks ahead for a directed super send bytecode
- 	 and does not generate any code for the dereference yet if followed by a directed super send."
- 	<inline: false>
- 	self nextDescriptorExtensionsAndNextPCInto:
- 		[:descriptor :exta :extb :followingPC|
- 		(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
- 			[tempOop := self getLiteral: literalIndex.
- 			 ^0]].
- 	^self genPushLiteralVariable: literalIndex!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genSend: selectorIndex numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	self assert: (numArgs between: 0 and: 255). "say"
  	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
  	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
  	numArgs >= (NumSendTrampolines - 1) ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
+ 	 and: [annotation
+ 			between: IsDirectedSuperSend
+ 			and: IsDirectedSuperBindingSend]) ifTrue:
- 	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
  	self genLoadInlineCacheWithSelector: selectorIndex.
  	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendDirectedSuper:numArgs: (in category 'bytecode generator support') -----
  genSendDirectedSuper: selectorIndex numArgs: numArgs
  	<inline: false>
  	"N.B. genPushLiteralVariableGivenDirectedSuper: has already loaded tempOop with the association."
+ 	| result |
+ 	result := self
+ 				genSend: selectorIndex
+ 				numArgs: numArgs
+ 				sendTable: (directedSendUsesBinding
+ 								ifTrue: [directedSuperBindingSendTrampolines]
+ 								ifFalse: [directedSuperSendTrampolines]).
+ 	directedSendUsesBinding := false.
+ 	^result!
- 	^self genSend: selectorIndex numArgs: numArgs sendTable: directedSuperSendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	NumSpecialSelectors := 32.
  	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"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef		needsFrameNever: 1)
+ 		(1  16   31 genPushLiteralVariable16CasesBytecode			needsFrameNever: 1)
- 		(1  16   31 genPushLitVarDirSup16CasesBytecode				needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode					needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode				needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode							needsFrameNever: 1)
  		(1  77   77 genPushConstantTrueBytecode						needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode					needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode						needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode						needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode						needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode								needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 120 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 121 127 genSpecialSelectorSend isMapped) "#value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef is1ByteInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
  		
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)		"Needs a frame for context inst var access"
+ 		(2 227 227 genExtPushLiteralVariableBytecode			needsFrameNever: 1)
- 		(2 227 227 genExtPushLitVarDirSupBytecode			needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 unknownBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 genExtEnsureAllocableSlots isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genSistaExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 241 241 genSistaExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genSistaExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 244 244 genSistaExtStoreLiteralVariableBytecode isMappedIfImmutability)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 genExtPushFullClosureBytecode)
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genExtPushRemoteTempOrInstVarLongBytecode)
  		(3 252 252 genExtStoreRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  		(3 253 253 genExtStoreAndPopRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  
  		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsBytecode branch v4:Long:BranchIfNotInstanceOf:Distance:)
  		
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genMarshalledSend: selectorIndex numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
  	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
  	numArgs >= (NumSendTrampolines - 1) ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
+ 	 and: [annotation
+ 			between: IsDirectedSuperSend
+ 			and: IsDirectedSuperBindingSend]) ifTrue:
- 	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
  	self genLoadInlineCacheWithSelector: selectorIndex.
  	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
  	self voidReceiverOptStatus.
  	^self ssPushRegister: ReceiverResultReg!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPushLiteralIndex: (in category 'bytecode generator support') -----
+ genPushLiteralIndex: literalIndex "<SmallInteger>"
+ 	"Override to avoid the BytecodeSetHasDirectedSuperSend check, which is unnecessary
+ 	 here given the simulation stack."
+ 	<inline: false>
+ 	| literal |
+ 	literal := self getLiteral: literalIndex.
+ 	^self genPushLiteral: literal!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushLiteralVariable: (in category 'bytecode generator support') -----
  genPushLiteralVariable: literalIndex
  	<inline: false>
  	| association freeReg |
- 	freeReg := self allocateRegNotConflictingWith: 0.
  	association := self getLiteral: literalIndex.
+ 	"If followed by a directed super send bytecode, avoid generating any code yet.
+ 	 The association will be passed to the directed send trampoline in a register
+ 	 and fully dereferenced only when first linked.  It will be ignored in later sends."
+ 	BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[self deny: directedSendUsesBinding.
+ 		 self nextDescriptorExtensionsAndNextPCInto:
+ 			[:descriptor :exta :extb :followingPC|
+ 			(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
+ 				[self ssPushConstant: association.
+ 				 directedSendUsesBinding := true.
+ 				 ^0]]].
+ 	freeReg := self allocateRegNotConflictingWith: 0.
  	"N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods."
  	"So far descriptors are not rich enough to describe the entire dereference so generate the register
  	 load but don't push the result.  There is an order-of-evaluation issue if we defer the dereference."
  	self genMoveConstant: association R: TempReg.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: TempReg
  		scratchReg: freeReg.
  	objectRepresentation
  		genLoadSlot: ValueIndex
  		sourceReg: TempReg
  		destReg: freeReg.
  	self ssPushRegister: freeReg.
  	^0!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushLiteralVariableGivenDirectedSuper: (in category 'bytecode generator support') -----
- genPushLiteralVariableGivenDirectedSuper: literalIndex
- 	"This is a version of genPushLiteralVariable: that looks ahead for a directed super send bytecode
- 	 and does not generate any code for the dereference yet if followed by a directed super send."
- 	<inline: false>
- 	self nextDescriptorExtensionsAndNextPCInto:
- 		[:descriptor :exta :extb :followingPC|
- 		(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
- 			[self ssPushConstant: (self getLiteral: literalIndex).
- 			 ^0]].
- 	^self genPushLiteralVariable: literalIndex!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendDirectedSuper:numArgs: (in category 'bytecode generator support') -----
  genSendDirectedSuper: selectorIndex numArgs: numArgs
+ 	| result |
  	self assert: self ssTop type = SSConstant.
  	tempOop := self ssTop constant.
  	self ssPop: 1.
  	self marshallSendArguments: numArgs.
+ 	result := self
+ 				genMarshalledSend: selectorIndex
+ 				numArgs: numArgs
+ 				sendTable: (directedSendUsesBinding
+ 								ifTrue: [directedSuperBindingSendTrampolines]
+ 								ifFalse: [directedSuperSendTrampolines]).
+ 	directedSendUsesBinding := false.
+ 	^result!
- 	^self genMarshalledSend: selectorIndex numArgs: numArgs sendTable: directedSuperSendTrampolines!

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



More information about the Vm-dev mailing list