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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 6 20:20:04 UTC 2014


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

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

Name: VMMaker.oscog-eem.971
Author: eem
Time: 6 December 2014, 12:17:14.424 pm
UUID: ed756b25-4d7e-45a8-8a3b-c06199675128
Ancestors: VMMaker.oscog-eem.970

Fix a devilishly tricky bug with 32-bit Spur and PICs
in the Cogit.  In 32-bit Spur only zero is a valid cache
tag, that for Characters, due to SmallIntegers having
both 2r11 and 2r01 as valid tags.  The cache check
prolog collapses these down onto 1 by anding with
1 and hence collapses Character's 2r10 to 0.

The cache tag is also tested in the PIC abort routine
to distinguish between an MNU abort and an interpret
abort.  A PIC MNU entry jumps to code that first zeros
the cache tag (held in ClassReg) before calling the
abort routine, which tests ClassReg and selects the
relevant abort processing.

Hence in 32-bit Spur if a send site is linked for
Character and later extended to a PIC with an
interpret case, that interpret case will instead invoke
MNU processing.  This is rare; first there needs to be a
send to a CHaracter, then a send to something else
which binds to something that must be interpreted.
Ouch.

The fix is simple; if a send site that was linked with a
zero cache tag (which can only happen in 32-bit Spur)
link to an open PIC instead of to a closed PIC, or in the
case of an MNU do not link.

Changes:
Rename compilePICProlog:, mnuCall and interpretCall to
the more accurate compilePICAbort:, picMNUAbort and
picInterpretAbort.  Coment compilePICAbort: and
compileAbort. Name the zero value
picAbortDiscriminatorValue to make the code more
comprehensible/browsable.

Assert that the cache tag is not zero in ceCPICMiss:...

Refactor cogMNUPICSelector:methodOperand:numArgs:
to add receiver: parameter for the check for a zero
cache tag.

Eliminate some duplication introduced in early versions
of the ARM abort code.  Specifically lose sendMissCall
mnuCall interpretCall & interpretLabel.

Fix image load for Spur32BitMMLECoSimulator.

Fix type regression in cogMethodOf: with
cCoerceSimple:to:; CogClass's version should be
marked <doNotGenerate>.

Fix type warnings in primitiveCopyObject and
printStackCallStackOf:.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	| classTag 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.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					super: superNormalBar
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self assert: superNormalBar = 0.
  				^self
  					ceSend: selector
  					super: superNormalBar
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 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: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(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: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CogClass>>cCoerceSimple:to: (in category 'translation support') -----
  cCoerceSimple: value to: cTypeString
+ 	<doNotGenerate>
  	"Type coercion for translation and simulation.
  	 For simulation answer a suitable surrogate for the struct types"
  	^cTypeString caseOf:
  	   {	[#'unsigned long']							->	[value].
  		[#sqInt]										->	[value].
  		[#usqInt]									->	[value].
  		[#sqLong]									->	[value].
  		[#usqLong]									->	[value].
  		[#'AbstractInstruction *']					->	[value].
  		[#'BytecodeFixup *']						->	[value].
  		[#'CogMethod *']							->	[value].
  		[#'char *']									->	[value].
  		[#'sqInt *']									->	[value].
  		[#'void *']									->	[value].
  		[#void]										->	[value].
  		[#'void (*)()']								->	[value].
  		[#'void (*)(void)']							->	[value].
  		[#'unsigned long (*)(void)']					->	[value].
  		[#'void (*)(unsigned long,unsigned long)']	->	[value] }!

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

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

Item was changed:
  ----- Method: Cogit>>cCoerce:to: (in category 'simulation only') -----
  cCoerce: value to: cTypeString
+ 	"Type coercion. For translation a cast will be emmitted. When running in Smalltalk
+ 	  answer a suitable wrapper for correct indexing."
- 	"Type coercion for translation only; just return the value when running in Smalltalk."
  	<doNotGenerate>
+ 	^value
+ 		ifNil: [value]
+ 		ifNotNil: [value coerceTo: cTypeString sim: objectMemory]!
- 	^value == nil
- 		ifTrue: [value]
- 		ifFalse: [value coerceTo: cTypeString sim: objectMemory]!

Item was changed:
  ----- Method: Cogit>>ceCPICMiss:receiver: (in category 'in-line cacheing') -----
  ceCPICMiss: cPIC receiver: receiver
  	"Code entry closed PIC miss.  A send has fallen
  	 through a closed (finite) polymorphic inline cache.
  	 Either extend it or patch the send site to an open PIC.
  	 The stack looks like:
  			receiver
  			args
  	  sp=>	sender return address"
  	<var: #cPIC type: #'CogMethod *'>
  	<api>
  	| outerReturn newTargetMethodOrNil errorSelectorOrNil cacheTag result |
  	self cCode: ''
  		inSmalltalk:
  			[cPIC isInteger ifTrue:
  				[^self ceCPICMiss: (self cogMethodSurrogateAt: cPIC) receiver: receiver]].
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	outerReturn := coInterpreter stackTop.
+ 	self deny: (backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue. 
  	cPIC cPICNumCases < numPICCases
  		ifTrue:
  			[self lookup: cPIC selector
  				for: receiver
  				methodAndErrorSelectorInto:
  					[:method :errsel|
  					newTargetMethodOrNil := method.
  					errorSelectorOrNil := errsel]]
  		ifFalse: [newTargetMethodOrNil := errorSelectorOrNil := nil].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	(cPIC cPICNumCases >= numPICCases
  	 or: [(errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: cPIC selector
  					numArgs: cPIC cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	"Now extend the PIC with the new case."
  	self cogExtendPIC: cPIC
  		CaseNMethod: newTargetMethodOrNil
  		tag: cacheTag
  		isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  	"Jump back into the pic at its entry in case this is an MNU."
  	coInterpreter
  		executeCogMethod: cPIC
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

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

Item was removed:
- ----- Method: Cogit>>cogMNUPICSelector:methodOperand:numArgs: (in category 'in-line cacheing') -----
- cogMNUPICSelector: selector methodOperand: methodOperand numArgs: numArgs
- 	<api>
- 	"Attempt to create a one-case PIC for an MNU.
- 	 The tag for the case is at the send site and so doesn't need to be generated."
- 	<returnTypeC: #'CogMethod *'>
- 	| startAddress headerSize size end |
- 	(objectMemory isYoung: selector) ifTrue:
- 		[^0].
- 	coInterpreter
- 		compilationBreak: selector
- 		point: (objectMemory numBytesOf: selector)
- 		isMNUCase: true.
- 	self assert: endCPICCase0 notNil.
- 	startAddress := methodZone allocate: closedPICSize.
- 	startAddress = 0 ifTrue:
- 		[coInterpreter callForCogCompiledCodeCompaction.
- 		 ^0].
- 	methodLabel
- 		address: startAddress;
- 		dependent: nil.
- 	"stack allocate the various collections so that they
- 	 are effectively garbage collected on return."
- 	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
- 	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 		methodOperand: methodOperand
- 		numArgs: numArgs.
- 	self computeMaximumSizes.
- 	headerSize := self sizeof: CogMethod.
- 	size := self generateInstructionsAt: startAddress + headerSize.
- 	end := self outputInstructionsAt: startAddress + headerSize.
- 	"The missOffset is the same as the interpretOffset."
- 	self assert: missOffset = (interpretCall address + interpretCall machineCodeSize - startAddress).
- 	self assert: startAddress + cmEntryOffset = entry address.
- 	^self
- 		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 		size: closedPICSize
- 		numArgs: numArgs
- 		numCases: 1
- 		hasMNUCase: true
- 		selector: selector !

Item was added:
+ ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
+ cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
+ 	<api>
+ 	"Attempt to create a one-case PIC for an MNU.
+ 	 The tag for the case is at the send site and so doesn't need to be generated."
+ 	<returnTypeC: #'CogMethod *'>
+ 	| startAddress headerSize size end |
+ 	((objectMemory isYoung: selector)
+ 	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
+ 		[^0].
+ 	coInterpreter
+ 		compilationBreak: selector
+ 		point: (objectMemory numBytesOf: selector)
+ 		isMNUCase: true.
+ 	self assert: endCPICCase0 notNil.
+ 	startAddress := methodZone allocate: closedPICSize.
+ 	startAddress = 0 ifTrue:
+ 		[coInterpreter callForCogCompiledCodeCompaction.
+ 		 ^0].
+ 	methodLabel
+ 		address: startAddress;
+ 		dependent: nil.
+ 	"stack allocate the various collections so that they
+ 	 are effectively garbage collected on return."
+ 	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
+ 	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
+ 		methodOperand: methodOperand
+ 		numArgs: numArgs.
+ 	self computeMaximumSizes.
+ 	headerSize := self sizeof: CogMethod.
+ 	size := self generateInstructionsAt: startAddress + headerSize.
+ 	end := self outputInstructionsAt: startAddress + headerSize.
+ 	"The missOffset is the same as the interpretOffset."
+ 	self assert: missOffset = (picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
+ 	self assert: startAddress + cmEntryOffset = entry address.
+ 	^self
+ 		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
+ 		size: closedPICSize
+ 		numArgs: numArgs
+ 		numCases: 1
+ 		hasMNUCase: true
+ 		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress headerSize size end |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	headerSize := self sizeof: CogMethod.
  	size := self generateInstructionsAt: startAddress + headerSize.
  	end := self outputInstructionsAt: startAddress + headerSize.
  	"The missOffset is th same as the interpretOffset."
+ 	self assert: missOffset = (picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
- 	self assert: missOffset = (interpretCall address + interpretCall machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: endCPICCase0 address = (startAddress + firstCPICCaseOffset).
  	self assert: endCPICCase1 address = (startAddress + firstCPICCaseOffset + cPICCaseSize).
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		size: closedPICSize
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>compileAbort (in category 'compile abstract instructions') -----
  compileAbort
  	"The start of a CogMethod has a call to a run-time abort routine that either
  	 handles an in-line cache failure or a stack overflow.  The routine selects the
  	 path depending on ReceiverResultReg; if zero it takes the stack overflow
  	 path; if nonzero the in-line cache miss path.  Neither of these paths returns.
  	 The abort routine must be called;  In the callee the method is located by
+ 	 adding the relevant offset to the return address of the call.
+ 
+ 	 N.B. This code must match that in compilePICAbort: so that the offset of the
+ 	 return address of the call is the same in methods and closed PICs."
+ 	<returnTypeC: #'AbstractInstruction *'>
- 	 adding the relevant offset to the return address of the call."
  	stackOverflowCall := self MoveCq: 0 R: ReceiverResultReg.
  	backEnd hasLinkRegister
  		ifTrue:
+ 			["If there is a link register it must be saved (pushed onto the stack) before it
+ 			  is smashed by the abort call, and hence needs to be manually handled here"
+ 			 sendMiss := self PushR: LinkReg.
+ 			 ^self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]
- 			["if we have a link register we will assume that it does not get automatically pushed onto the stack
- 			and thus needs to be manually handled here"
- 			sendMiss := self PushR: LinkReg.
- 			 sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]
  		ifFalse:
+ 			[^sendMiss := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]!
- 			[sendMiss :=
- 			 sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]!

Item was changed:
  ----- Method: Cogit>>compileCPIC:Case0:Case1Method:tag:isMNUCase:numArgs: (in category 'in-line cacheing') -----
  compileCPIC: cPIC Case0: case0CogMethod Case1Method: case1Method tag: case1Tag isMNUCase: isMNUCase numArgs: numArgs
  	"Compile the code for a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; jump to its unchecked entry-point
  		- a CompiledMethod; jump to the ceInterpretFromPIC trampoline
  		- nil; call ceMNUFromPIC"
  	<var: #cPIC type: #'CogMethod *'>
  	| operand targetEntry jumpNext |
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<var: #targetEntry type: #'void *'>
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	self assert: case1Method notNil.
+ 	self compilePICAbort: numArgs.
- 	self compilePICProlog: numArgs.
  	self assert: (objectRepresentation inlineCacheTagIsYoung: case1Tag) not.
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: case1Method])
  		ifTrue:
  			[operand := 0.
  			 targetEntry := ((coInterpreter cogMethodOf: case1Method) asInteger + cmNoCheckEntryOffset) asVoidPointer]
  		ifFalse:
  			[self assert: (case1Method isNil or: [(objectMemory isYoungObject: case1Method) not]).
  			 operand := case1Method.
+ 			 targetEntry := case1Method isNil ifTrue: [picMNUAbort] ifFalse: [picInterpretAbort]].
- 			 targetEntry := case1Method isNil ifTrue: [mnuCall] ifFalse: [interpretLabel]].
  
  	jumpNext := self compileCPICEntry.
  	self MoveCw: 0 R: SendNumArgsReg.
  	self JumpLong: case0CogMethod asInteger + cmNoCheckEntryOffset.
  	endCPICCase0 := self CmpCw: case1Tag R: TempReg.
  	jumpNext jmpTarget: endCPICCase0.
  	self MoveCw: operand R: SendNumArgsReg.
+ 	self JumpLongZero: (isMNUCase ifTrue: [picMNUAbort] ifFalse: [targetEntry]) asInteger.
- 	self JumpLongZero: (isMNUCase ifTrue: [mnuCall] ifFalse: [targetEntry]) asInteger.
  	endCPICCase1 := self MoveCw: cPIC asInteger R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0
  !

Item was changed:
  ----- Method: Cogit>>compileClosedPICPrototype (in category 'in-line cacheing') -----
  compileClosedPICPrototype
  	"Compile the abstract instructions for a full closed PIC used to initialize closedPICSize.
  	 The loads into SendNumArgsReg are those for optional method objects which may be
  	 used in MNU cases."
  	| numArgs jumpNext |
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	numArgs := 0.
+ 	self compilePICAbort: numArgs.
- 	self compilePICProlog: numArgs.
  	jumpNext := self compileCPICEntry.
  	self MoveCw: 16r5EAF00D R: SendNumArgsReg.
  	self JumpLong: 16r5EEDCA5E.
  	jumpNext jmpTarget: (endCPICCase0 := self Label).
  	1 to: numPICCases - 1 do:
  		[:h|
  		self CmpCw: 16rBABE1F15+h R: TempReg.
  		self MoveCw: 16rBADA550 + h R: SendNumArgsReg.
  		self JumpLongZero: 16rBEDCA5E0.
  		h = 1 ifTrue:
  			[endCPICCase1 := self Label]].
  	self MoveCw: 16rAB5CE55 R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0!

Item was changed:
  ----- Method: Cogit>>compileMNUCPIC:methodOperand:numArgs: (in category 'in-line cacheing') -----
  compileMNUCPIC: cPIC methodOperand: methodOperand numArgs: numArgs
  	"Compile the code for a one-case MNU PIC that calls ceMNUFromPIC for case0Tag
  	 The tag for case0 is at the send site and so doesn't need to be generated."
  	<var: #cPIC type: #'CogMethod *'>
  	| jumpNext |
  	<var: #jumpNext type: #'AbstractInstruction *'>
+ 	self compilePICAbort: numArgs.
- 	self compilePICProlog: numArgs.
  	jumpNext := self compileCPICEntry.
  	self MoveCw: methodOperand R: SendNumArgsReg.
+ 	self JumpLong: picMNUAbort asInteger.
- 	self JumpLong: mnuCall asInteger.
  	jumpNext jmpTarget: (self MoveCw: cPIC asInteger R: ClassReg).
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0
  !

Item was added:
+ ----- Method: Cogit>>compilePICAbort: (in category 'in-line cacheing') -----
+ compilePICAbort: numArgs
+ 	"The start of a PIC has a call to a run-time abort routine that either handles a dispatch to an
+ 	 interpreted method or a dispatch of an MNU case.  The routine selects the path by testing
+ 	 ClassReg, which holds the inline cache tag; if equal to the picAbortDiscriminatorValue (zero)
+ 	 it takes the MNU path; if nonzero the dispatch to interpreter path.  Neither of these paths
+ 	 returns. The abort routine must be called;  In the callee the PIC is located by adding the
+ 	 relevant offset to the return address of the call.
+ 
+ 	 N.B. This code must match that in compileAbort so that the offset of the return address of
+ 	 the call is the same in methods and closed PICs."
+ 	picMNUAbort := self MoveCq: self picAbortDiscriminatorValue R: ClassReg.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			["If there is a link register it must be saved (pushed onto the stack) before it
+ 			  is smashed by the abort call, and hence needs to be manually handled here".
+ 			 picInterpretAbort := self PushR: LinkReg.
+ 			 self Call: (self picAbortTrampolineFor: numArgs)]
+ 		ifFalse:
+ 			[picInterpretAbort := self Call: (self picAbortTrampolineFor: numArgs)].
+ 	^0!

Item was removed:
- ----- Method: Cogit>>compilePICProlog: (in category 'in-line cacheing') -----
- compilePICProlog: numArgs
- 	"The start of a PIC has a call to a run-time abort routine that either handles
- 	 a dispatch to an interpreted method or a dispatch of an MNU case.  The
- 	 routine selects the path depending on ClassReg; if zero it takes the MNU
- 	 path; if nonzero the dispatch to interpreter path.  Neither of these paths
- 	 returns. The abort routine must be called;  In the callee the PIC is located
- 	 by adding the relevant offset to the return address of the call."
- 	mnuCall := self MoveCq: 0 R: ClassReg.
- 	backEnd hasLinkRegister
- 		ifTrue:
- 			["if we have a link register we will assume that it does not get automatically pushed onto the stack
- 			and thus needs to be manually handled here"
- 			 interpretLabel := self PushR: LinkReg.
- 			 interpretCall := self Call: (self picAbortTrampolineFor: numArgs)]
- 		ifFalse:
- 			[interpretLabel :=
- 			 interpretCall := self Call: (self picAbortTrampolineFor: numArgs)].
- 	^0!

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

Item was changed:
  ----- Method: Cogit>>genInnerPICAbortTrampoline: (in category 'initialization') -----
  genInnerPICAbortTrampoline: name
  	"Generate the abort for a PIC.  This abort performs either a call of
+ 	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged target
+ 	 or a call of ceMNUFromPICMNUMethod:receiver: to handle an MNU dispatch
+ 	 in a closed PIC.  It distinguishes the two by testing ClassReg.  If the register
+ 	 is zero then this is an MNU.
+ 	
+ 	 This poses a problem in 32-bit Spur, where zero is the cache tag for immediate
+ 	 characters (tag pattern 2r10) because SmallIntegers have tag patterns 2r11
+ 	 and 2r01, so anding with 1 reduces these to 0 & 1.  We solve the ambiguity by
+ 	 patching send sites with a 0 cache tag to open PICs instead of closed PICs."
- 	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
- 	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
- 	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
- 	 ClassReg.  If the register is zero then this is an MNU."
  	<var: #name type: #'char *'>
  	| jumpMNUCase |
  	<var: #jumpMNUCase type: #'AbstractInstruction *'>
+ 	self CmpCq: self picAbortDiscriminatorValue R: ClassReg.
- 	self CmpCq: 0 R: ClassReg.
  	jumpMNUCase := self JumpZero: 0.
  	self compileTrampolineFor: #ceInterpretMethodFromPIC:receiver:
  		numArgs: 2
  		arg: SendNumArgsReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil.
  	jumpMNUCase jmpTarget: self Label.
  	^self genTrampolineFor: #ceMNUFromPICMNUMethod:receiver:
  		called: name
  		numArgs: 2
  		arg: SendNumArgsReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was added:
+ ----- Method: Cogit>>picAbortDiscriminatorValue (in category 'accessing') -----
+ picAbortDiscriminatorValue
+ 	"This value is used to decide between MNU processing
+ 	 or interpretation in the closed PIC aborts."
+ 	^0!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveCopyObject (in category 'object access primitives') -----
  primitiveCopyObject
  	"Primitive. Copy the state of the receiver from the argument. 
  		Fail if receiver and argument are of a different class.
  		Fail if the receiver or argument are contexts (because of context-to-stack mapping).
  		Fail if receiver and argument have different lengths (for indexable objects).
  		Fail if the objects are not in a fit state to be copied (e.g. married contexts and Cogged methods)"
  	| rcvr arg length |
  	self methodArgumentCount >= 1 ifFalse:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	arg := self stackTop.
  	rcvr := self stackValue: 1.
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
  	(objectMemory isImmediate: arg) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
  	(objectMemory fetchClassTagOfNonImm: rcvr)
  		~= (objectMemory fetchClassTagOfNonImm: arg) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
  	(objectMemory isWordsOrBytesNonImm: rcvr)
  		ifTrue:
  			[length := objectMemory numBytesOf: rcvr.
  			((objectMemory formatOf: rcvr) = (objectMemory formatOf: arg)
  			  and: [length = (objectMemory numBytesOf: arg)]) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument].
+ 			 self mem: (rcvr + objectMemory baseHeaderSize) asVoidPointer
+ 				cp: (arg + objectMemory baseHeaderSize) asVoidPointer
- 			 self mem: rcvr + objectMemory baseHeaderSize
- 				cp: arg + objectMemory baseHeaderSize
  				y: length]
  		ifFalse:
  			[(self isAppropriateForCopyObject: rcvr) ifFalse:
  				[^self primitiveFailFor: PrimErrBadReceiver].
  			 length := objectMemory numSlotsOf: rcvr.
  			 ((self isAppropriateForCopyObject: arg)
  			  and: [length = (objectMemory lengthOf: arg)]) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument].
  			 0 to: length - 1 do:
  				[:i|
  				objectMemory
  					storePointer: i
  					ofObject: rcvr
  					withValue: (objectMemory fetchPointer: i ofObject: arg)]].
  
  	"Note: The above could be faster for young receivers but I don't think it'll matter"
  	self pop: self methodArgumentCount "pop arg; answer receiver"!

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

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>nextLongFrom: (in category 'initialization') -----
+ nextLongFrom: aStream
+ 	"Read a 32- or 64-bit quantity from the given (binary) stream."
+ 
+ 	^aStream nextLittleEndianNumber: self wordSize!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>nextWord32From: (in category 'initialization') -----
+ nextWord32From: aStream
+ 	"Read a 32-bit quantity from the given (binary) stream."
+ 
+ 	^aStream nextLittleEndianNumber: 4!

Item was changed:
  ----- Method: SpurMemoryManager>>cCoerce:to: (in category 'memory access') -----
  cCoerce: value to: cTypeString
  	"Type coercion. For translation a cast will be emmitted. When running in Smalltalk
  	  answer a suitable wrapper for correct indexing."
+ 	<doNotGenerate>
- 
  	^value
  		ifNil: [value]
  		ifNotNil: [value coerceTo: cTypeString sim: self]!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStackOf: (in category 'debug printing') -----
  printStackCallStackOf: frameOrContext
  	<api>
  	| theFP context |
  	<var: #theFP type: #'char *'>
  	(objectMemory addressCouldBeObj: frameOrContext) ifTrue:
  		[((objectMemory isContext: frameOrContext)
  		  and: [self checkIsStillMarriedContext: frameOrContext currentFP: nil]) ifTrue:
+ 			[^self printStackCallStackOf: (self frameOfMarriedContext: frameOrContext) asInteger].
- 			[^self printStackCallStackOf: (self frameOfMarriedContext: frameOrContext)].
  		 ^nil].
  	 
  	theFP := frameOrContext asVoidPointer.
  	[context := self shortReversePrintFrameAndCallers: theFP.
  	 ((self isMarriedOrWidowedContext: context)
  	  and:
  		[theFP := self frameOfMarriedContext: context.
  		 self checkIsStillMarriedContext: context currentFP: theFP]) ifFalse:
  			[^nil]] repeat!

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



More information about the Vm-dev mailing list