[Vm-dev] VM Maker: VMMaker.oscog-cb.1797.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 11 23:20:27 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1797.mcz

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

Name: VMMaker.oscog-cb.1797
Author: cb
Time: 11 April 2016, 4:18:50.709039 pm
UUID: c057f777-22a9-4372-bb3d-958cee4fb0f0
Ancestors: VMMaker.oscog-cb.1796

- Fix a slip in CogIA32Compiler printing (machineCodeAt: got misplaced somehow)
- Add API to do in-image compilation for full block closure
- fix the machine code generation of full block closure value primitive and add the SistaV1BytecodeSet option
- Fix a slip in machine code zone compaction of primitives.
- Various fixes related to full block closures

=============== Diff against VMMaker.oscog-cb.1796 ===============

Item was changed:
  ----- Method: CoInterpreter>>activateNewFullClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod."
+ 	| numCopied theMethod methodHeader numTemps inInterpreter switched |
- 	| numCopied theMethod methodHeader numTemps |
  	<inline: true>
  	numCopied := self copiedValueCountOfFullClosure: blockClosure.
  	theMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
  	self assert: (objectMemory isOopCompiledMethod: theMethod).
  	methodHeader := self rawHeaderOf: theMethod.
  	(self isCogMethodReference: methodHeader) ifTrue:
  		[^self
  			executeFullCogBlock: (self cogMethodOf: theMethod)
  			closure: blockClosure
  			mayContextSwitch: mayContextSwitch].
  	"How do we know when to compile a block method?
  	 One simple criterion is to check if the block is running within its inner context,
  	 i.e. if the outerContext is married.
  	 Even simpler is to remember the previous block entered via the interpreter and
  	 compile if this is the same one.  But we can thrash trying to compile an uncoggable
  	 method unless we try and remember which ones can't be cogged.  So also record
  	 the last block method we failed to compile and avoid recompiling it."
  	(self methodWithHeaderShouldBeCogged: methodHeader)
  		ifTrue:
  			[theMethod = lastCoggableInterpretedBlockMethod
  				ifTrue:
  					[theMethod ~= lastUncoggableInterpretedBlockMethod ifTrue:
  						[cogit cogFullBlockMethod: theMethod numCopied: numCopied.
  						 (self methodHasCogMethod: theMethod) ifTrue:
  							[^self executeFullCogBlock: (self cogMethodOf: theMethod)
  								closure: blockClosure
  								mayContextSwitch: mayContextSwitch].
  						 cogCompiledCodeCompactionCalledFor ifFalse:
  							[lastUncoggableInterpretedBlockMethod := theMethod]]]
  				ifFalse:
  					[lastCoggableInterpretedBlockMethod := theMethod]]
  		ifFalse:
  			[self maybeFlagMethodAsInterpreted: theMethod].
  
+ 	self assert: (self methodHasCogMethod: theMethod) not.
+ 	"Because this is an uncogged method we need to continue via the interpreter.
+ 	 We could have been reached either from the interpreter, in which case we
+ 	 should simply return, or from a machine code frame or from a compiled
+ 	 primitive.  In these latter two cases we must longjmp back to the interpreter.
+ 	 The instructionPointer tells us which path we took.
+ 	 If the sender was an interpreter frame but called through a (failing) primitive
+ 	 then make sure we restore the saved instruction pointer and avoid pushing
+ 	 ceReturnToInterpreterPC which is only valid between an interpreter caller
+ 	 frame and a machine code callee frame."
+ 	(inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
+ 		[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
+ 			[instructionPointer := self iframeSavedIP: framePointer]].
+ 
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
  	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: FullClosureReceiverIndex ofObject: blockClosure).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + FullClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	methodHeader := objectMemory methodHeaderOf: theMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	numArgs + numCopied + 1 to: numTemps do: [ :i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: theMethod) - 1.
  	
  	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
+ 	switched := false.
  	stackPointer < stackLimit ifTrue:
+ 		[switched := self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch].
+ 	self returnToExecutive: inInterpreter postContextSwitch: switched!
- 		[self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch]!

Item was added:
+ ----- Method: CogIA32Compiler>>machineCodeAt: (in category 'accessing') -----
+ machineCodeAt: anOffset
+ 	^machineCode at: anOffset!

Item was removed:
- ----- Method: CogIA32CompilerForTests>>machineCodeAt: (in category 'accessing') -----
- machineCodeAt: anOffset
- 	^machineCode at: anOffset!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFullClosureValue (in category 'primitive generators') -----
  genPrimitiveFullClosureValue
  	"Defer to the cogit for this one, to match the split for genPrimitiveClosureValue."
  	<doNotGenerate>
+ 	<option: #SistaV1BytecodeSet>
  	^cogit genPrimitiveFullClosureValue!

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 callerSavedRegMask 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 cPICEndSize 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 ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod'
- 	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 callerSavedRegMask postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockStackOverflowCall fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cPICEndSize 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 ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod'
  	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 MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' 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 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>>cog:options: (in category 'in-image compilation') -----
  cog: aCompiledMethod options: optionsArray
+ 	^self cog: aCompiledMethod selectorOrNumCopied: aCompiledMethod selector options: optionsArray!
- 	^self cog: aCompiledMethod selector: aCompiledMethod selector options: optionsArray!

Item was changed:
  ----- Method: Cogit class>>cog:selector: (in category 'in-image compilation') -----
  cog: aCompiledMethod selector: aSelector
+ 	^self cog: aCompiledMethod selectorOrNumCopied: aSelector options: #()!
- 	^self cog: aCompiledMethod selector: aSelector options: #()!

Item was removed:
- ----- Method: Cogit class>>cog:selector:options: (in category 'in-image compilation') -----
- cog: aCompiledMethod selector: aSelector options: optionsDictionaryOrArray
- 	"StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
- 	| cogit coInterpreter |
- 	cogit := self instanceForTests: optionsDictionaryOrArray.
- 	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
- 	[cogit
- 		setInterpreter: coInterpreter;
- 		singleStep: true;
- 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size / 2. "leave space for rump C stack"
- 	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
- 		on: Notification
- 		do: [:ex|
- 			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
- 				[ex resume: coInterpreter].
- 			ex pass].
- 	^{ coInterpreter.
- 		cogit.
- 		cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: aSelector) }!

Item was added:
+ ----- Method: Cogit class>>cog:selectorOrNumCopied:options: (in category 'in-image compilation') -----
+ cog: aCompiledMethod selectorOrNumCopied: selectorOrNumCopied options: optionsDictionaryOrArray
+ 	"StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
+ 	| cogit coInterpreter |
+ 	cogit := self instanceForTests: optionsDictionaryOrArray.
+ 	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
+ 	[cogit
+ 		setInterpreter: coInterpreter;
+ 		singleStep: true;
+ 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size / 2. "leave space for rump C stack"
+ 	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
+ 		on: Notification
+ 		do: [:ex|
+ 			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
+ 				[ex resume: coInterpreter].
+ 			ex pass].
+ 	^{ coInterpreter.
+ 		cogit.
+ 		selectorOrNumCopied isInteger
+ 			ifTrue: [ cogit cogFullBlockMethod: (coInterpreter oopForObject: aCompiledMethod) numCopied: selectorOrNumCopied ]
+ 			ifFalse: [ cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: selectorOrNumCopied) ] }!

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: 'unsigned long (*ceGetFP)(void)';
  		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 *)';
  		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'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
+ 					fullBlockNoContextSwitchEntry fullBlockEntry
- 					fullBlockStackOverflowCall 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]';
  		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]';
  		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)].
  	"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 added:
+ ----- Method: Cogit class>>genAndDis:numCopied:options: (in category 'in-image compilation') -----
+ genAndDis: compiledBlock numCopied: numCopied options: optionsDictionaryOrArray
+ 	| tuple |
+ 	tuple := self cog: compiledBlock selectorOrNumCopied: numCopied options: optionsDictionaryOrArray.
+ 	tuple second disassembleMethod: tuple last.
+ 	^tuple!

Item was changed:
  ----- Method: Cogit class>>genAndDis:options: (in category 'in-image compilation') -----
  genAndDis: methodOrDoitString options: optionsDictionaryOrArray
  	| tuple |
  	methodOrDoitString isCompiledMethod ifFalse:
  		[^self
  			genAndDis: (Compiler new
  							compiledMethodFor: methodOrDoitString
  							in: nil
  							to: nil
  							notifying: nil
  							ifFail: nil
  							logged: false)
  			 options: optionsDictionaryOrArray].
+ 	tuple := self cog: methodOrDoitString selectorOrNumCopied: methodOrDoitString selector options: optionsDictionaryOrArray.
- 	tuple := self cog: methodOrDoitString selector: methodOrDoitString selector options: optionsDictionaryOrArray.
  	tuple second disassembleMethod: tuple last.
  	^tuple!

Item was changed:
  ----- Method: Cogit class>>testPCMappingFor:options: (in category 'tests') -----
  testPCMappingFor: aCompiledMethod options: optionsDictionaryOrArray
  	| tuple |
+ 	tuple := self cog: aCompiledMethod selectorOrNumCopied: aCompiledMethod selector options: optionsDictionaryOrArray.
- 	tuple := self cog: aCompiledMethod selector: aCompiledMethod selector options: optionsDictionaryOrArray.
  	tuple second testPCMappingForCompiledMethod: aCompiledMethod cogMethod: tuple last!

Item was changed:
  ----- Method: Cogit>>cogFullBlockMethod:numCopied: (in category 'jit - api') -----
  cogFullBlockMethod: aMethodObj numCopied: numCopied
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self cCode: [] inSmalltalk: "for debugging, allow excluding methods based on selector or methodClass"
+ 		[self class initializationOptions
- 		[self halt class initializationOptions
  			at: #DoNotJIT
  			ifPresent:
  				[:excluded| 
  				(excluded anySatisfy: [:exclude| aMethodObj = exclude]) ifTrue:
  					[coInterpreter transcript nextPutAll: 'EXCLUDING '; nextPutAll: aMethodObj; nextPutAll: ' (compiled block)'; cr; flush.
  					 ^nil]]].
  	self deny: (coInterpreter methodHasCogMethod: aMethodObj).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	cogMethod := self compileCogFullBlockMethod: numCopied.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
  compileCogFullBlockMethod: numCopied
  	<returnTypeC: #'CogMethod *'>
  	| numBytecodes numBlocks numCleanBlocks result |
  	hasYoungReferent := (objectMemory isYoungObject: methodObj).
  	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
  	inBlock := true.
  	postCompileHook := nil.
  	maxLitIndex := -1.
  	self assert: (coInterpreter primitiveIndexOf: methodObj) = 0.
  	initialPC := coInterpreter startPCOfMethod: methodObj.
  	"initial estimate.  Actual endPC is determined in scanMethod."
  	endPC := objectMemory numBytesOf: methodObj.
  	numBytecodes := endPC - initialPC + 1.
+ 	primitiveIndex := 0.
  	self allocateOpcodes: (numBytecodes + 10) * self estimateOfAbstractOpcodesPerBytecodes
  		bytecodes: numBytecodes
  		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
+ 	self flag: #TODO. "currently copiedValue access implies frameful method, this is suboptimal"
  	(numBlocks := self scanMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
  	self assert: numBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
  	numCleanBlocks := self scanForCleanBlocks.
  	self assert: numCleanBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
  	self allocateBlockStarts: numBlocks + numCleanBlocks.
  	blockCount := 0.
  	numCleanBlocks > 0 ifTrue:
  		[self addCleanBlockStarts].
  	(self maybeAllocAndInitCounters
  	 and: [self maybeAllocAndInitIRCs]) ifFalse: "Inaccurate error code, but it'll do.  This will likely never fail."
  		[^coInterpreter cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireFullBlockMethod: numCopied) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogFullBlock!

Item was changed:
  ----- Method: Cogit>>compileFullBlockEntry (in category 'compile abstract instructions') -----
  compileFullBlockEntry
  	"Compile the abstract instructions for the entire method, including blocks."
  	| jumpNoContextSwitch |
  
  	"Abort for stack overflow on full block activation (no inline cache miss possible).
  	 The flag is SendNumArgsReg."
+ 	stackOverflowCall := self MoveCq: 0 R: ReceiverResultReg.
- 	fullBlockStackOverflowCall := self MoveCq: 0 R: ReceiverResultReg.
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	"Since the only case in which this is called is the
  	 stack overflow case we can reuse the trampoline."
  	self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs).
  
  	"Entries"
  	"No context switch entry"
  	fullBlockNoContextSwitchEntry := self MoveCq: 0 R: SendNumArgsReg.
  	jumpNoContextSwitch := self Jump: 0.
  
  	self AlignmentNops: (objectMemory wordSize max: 8).
  	"Context switch entry (use ReceiverResultReg as a non-zero value; it's shorter)."
  	fullBlockEntry := self MoveR: ReceiverResultReg R: SendNumArgsReg.
  	jumpNoContextSwitch jmpTarget: self Label.
  
  	^0!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function result savedFramePointer savedStackPointer savedArgumentCount rpc |
  	evaluable := simulatedTrampolines at: aProcessorSimulationTrap address.
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue:
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(function beginsWith: 'ceShort') ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	aProcessorSimulationTrap type = #call
  		ifTrue:
  			[processor
  				simulateCallOf: aProcessorSimulationTrap address
  				nextpc: aProcessorSimulationTrap nextpc
  				memory: coInterpreter memory.
  			self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
  				memory: coInterpreter memory.
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: coInterpreter memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter checkForLastObjectOverwrite.
  		 coInterpreter primFailCode = 0
  			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
+ 						primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
  						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  						primitiveExecuteMethodArgsArray primitiveExecuteMethod
  						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  							includes: function) ifFalse:
  						[self assert: savedFramePointer = coInterpreter framePointer.
  						 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  								= coInterpreter stackPointer]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  		 rpc := processor retpcIn: coInterpreter memory.
  		 self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
  		 processor
  			smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  			simulateReturnIn: coInterpreter memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  							ifNil: [0]
  							ifNotNil: [result isInteger
  										ifTrue: [result]
  										ifFalse: [16rF00BA222]])
  
  	"coInterpreter cr.
  	 processor sp + 32 to: processor sp - 32 by: -4 do:
  		[:sp|
  		 sp = processor sp
  			ifTrue: [coInterpreter print: 'sp->'; tab]
  			ifFalse: [coInterpreter printHex: sp].
  		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveFullClosureValue (in category 'primitive generators') -----
  genPrimitiveFullClosureValue
  	"Check the argument count.  Fail if wrong.
  	 Get the method from the outerContext and see if it is cogged.  If so, jump to the
  	 block entry or the no-context-switch entry, as appropriate, and we're done.  If not,
  	 invoke the interpreter primitive."
+ 	| jumpFailNArgs jumpFailImmediateMethod jumpFail4 jumpBCMethod primitiveRoutine result |
+ 	<option: #SistaV1BytecodeSet>
+ 	<var: #jumpFailImmediateMethod type: #'AbstractInstruction *'>
- 	| jumpFailNArgs jumpFail3 jumpFail4 jumpBCMethod primitiveRoutine result |
- 	<var: #jumpFail3 type: #'AbstractInstruction *'>
  	<var: #jumpFail4 type: #'AbstractInstruction *'>
  	<var: #jumpFailNArgs type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)()'>
  	objectRepresentation genLoadSlot: ClosureNumArgsIndex sourceReg: ReceiverResultReg destReg: TempReg.
  	self CmpCq: (objectMemory integerObjectOf: methodOrBlockNumArgs) R: TempReg.
  	jumpFailNArgs := self JumpNonZero: 0.
  
  	"We defer unforwarding the receiver to the prologue; scanning blocks
  	 for inst var refs and only unforwarding if the block refers to inst vars."
  	(false
  	 and: [objectRepresentation hasSpurMemoryManagerAPI]) ifTrue:
  		[objectRepresentation
  			genLoadSlot: FullClosureReceiverIndex sourceReg: ReceiverResultReg destReg: SendNumArgsReg;
  			genEnsureOopInRegNotForwarded: SendNumArgsReg
  			scratchReg: TempReg
  			updatingSlot: FullClosureReceiverIndex
  			in: ReceiverResultReg].
  	objectRepresentation genLoadSlot: FullClosureCompiledBlockIndex sourceReg: ReceiverResultReg destReg: SendNumArgsReg.
+ 	jumpFailImmediateMethod := objectRepresentation genJumpImmediate: SendNumArgsReg.
- 	jumpFail3 := objectRepresentation genJumpImmediate: SendNumArgsReg.
  	objectRepresentation genGetFormatOf: SendNumArgsReg into: TempReg.
  	self CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
  	jumpFail4 := self JumpLess: 0.
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpImmediate: ClassReg.
  
  	primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex.
  	self AddCq: (primitiveRoutine = #primitiveFullClosureValueNoContextSwitch
  					ifTrue: [self fullBlockNoContextSwitchEntryOffset]
  					ifFalse: [self fullBlockEntryOffset])
  		 R: ClassReg.
+ 	self JumpR: ClassReg.
+ 	jumpBCMethod jmpTarget: (jumpFailImmediateMethod jmpTarget: (jumpFail4 jmpTarget: self Label)).
- 	self JumpR: TempReg.
- 	jumpBCMethod jmpTarget: (jumpFail3 jmpTarget: (jumpFail4 jmpTarget: self Label)).
  	(result := self compileInterpreterPrimitive: primitiveRoutine) < 0 ifTrue:
  		[^result].
  	jumpFailNArgs jmpTarget: self Label.
  	^CompletePrimitive!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>rewritePrimInvocationIn:to: (in category 'external primitive support') -----
  rewritePrimInvocationIn: cogMethod to: primFunctionPointer
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #primFunctionPointer declareC: #'void (*primFunctionPointer)(void)'>
  	| primIndex flags address extent |
+ 	self cCode: [] inSmalltalk:
+ 		[primFunctionPointer isInteger ifFalse:
+ 			[^self rewritePrimInvocationIn: cogMethod to: (self simulatedTrampolineFor: primFunctionPointer)]].
  	self assert: cogMethod cmType = CMMethod.
  	primIndex := coInterpreter
  					primitiveIndexOfMethod: cogMethod methodObject
  					header: cogMethod methodHeader.
  	flags := coInterpreter primitivePropertyFlags: primIndex.
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[backEnd
  			storeLiteral: primFunctionPointer asUnsignedInteger
  			beforeFollowingAddress: cogMethod asUnsignedInteger
  									+ (externalSetPrimOffsets at: cogMethod cmNumArgs)].
  	"See compileInterpreterPrimitive:"
  	(flags anyMask: PrimCallMayCallBack)
  		ifTrue:
  			[address := cogMethod asUnsignedInteger
  						+ (externalPrimJumpOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteJumpFullAt: address
+ 						target: primFunctionPointer asUnsignedInteger]
- 						target: (self cCode: [primFunctionPointer asUnsignedInteger]
- 									inSmalltalk: [self simulatedTrampolineFor: primFunctionPointer])]
  		ifFalse:
  			[address := cogMethod asUnsignedInteger
  						+ (externalPrimCallOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteCallFullAt: address
+ 						target: primFunctionPointer asUnsignedInteger].
- 						target: (self cCode: [primFunctionPointer asUnsignedInteger]
- 									inSmalltalk: [self simulatedTrampolineFor: primFunctionPointer])].
  	processor
  		flushICacheFrom: cogMethod asUnsignedInteger + cmNoCheckEntryOffset
  		to: address asUnsignedInteger + extent!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveFullClosureValue (in category 'primitive generators') -----
  genPrimitiveFullClosureValue
  	"Override to push the register args first."
+ 	<option: #SistaV1BytecodeSet>
- 	self break.
  	self genPushRegisterArgs.
  	^super genPrimitiveFullClosureValue!



More information about the Vm-dev mailing list