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

commits at source.squeak.org commits at source.squeak.org
Mon Mar 30 01:43:12 UTC 2020


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

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

Name: VMMaker.oscog-eem.2734
Author: eem
Time: 29 March 2020, 6:42:58.093616 pm
UUID: ab7ba9fb-7121-4fb0-a741-c22da8b1fbd0
Ancestors: VMMaker.oscog-eem.2733

CoInterpeter: No longer rely on setjmp/longjmp to get back into the interpreter from arbitrary locatons.  Instead, since CoInterpreter maintains the base of the C stack in CFramePointer & CStackPointer, it is straight-forward for us to simply call interpret after doing the switch to the C stack, avoiding issues such as stack unwind problems in longjmp.  And of course the implementation is simpler thn setjmp/longjmp and so faster."

This commit adds the new machinery.  A subsequent commit will clean-up and delete the old machinery.

P.S. this change exposes what looks like a bug in the Bochs simulators, so currently neither x86 nor x64 simulate.  We shall have to fix this very soon.

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

Item was changed:
  ----- Method: CoInterpreter>>ceBaseFrameReturn: (in category 'trampolines') -----
  ceBaseFrameReturn: returnValue
  	"Return across a page boundary.  The context to return to (which may be married)
  	 is stored in the first word of the stack.  We get here when a return instruction jumps
  	 to the ceBaseFrameReturn: address that is the return pc for base frames.  A consequence
  	 of this is that the current frame is no longer valid since an interrupt may have overwritten
  	 its state as soon as the stack pointer has been cut-back beyond the return pc.  So to have
  	 a context to send the cannotReturn: message to we also store the base frame's context
  	 in the second word of the stack page."
  	<api>
  	| contextToReturnTo contextToReturnFrom isAContext thePage newPage frameAbove |
  	<var: #thePage type: #'StackPage *'>
  	<var: #newPage type: #'StackPage *'>
  	<var: #frameAbove type: #'char *'>
  	self assert: (stackPages stackPageFor: stackPointer) = stackPage.
  	self assert: stackPages mostRecentlyUsedPage = stackPage.
  	cogit assertCStackWellAligned.
  	self assert: framePointer = 0.
  	self assert: stackPointer <= (stackPage baseAddress - objectMemory wordSize).
  	self assert: stackPage baseFP + (2 * objectMemory wordSize) < stackPage baseAddress.
  	"We would like to use the following assert but we can't since the stack pointer will be above the
  	 base frame pointer in the base frame return and hence the 0 a base frame pointer points at could
  	 be overwritten which will cause the isBaseFrame assert in frameCallerContext: to fail."
  	"self assert: (self frameCallerContext: stackPage baseFP) = (stackPages longAt: stackPage baseAddress)."
  	self assert: ((objectMemory addressCouldBeObj: (stackPages longAt: stackPage baseAddress - objectMemory wordSize))
  				and: [objectMemory isContext: (stackPages longAt: stackPage baseAddress - objectMemory wordSize)]).
  	contextToReturnTo := stackPages longAt: stackPage baseAddress.
  	self assert: (objectMemory addressCouldBeObj: contextToReturnTo).
  
  	"The stack page is effectively free now, so free it.  We must free it to be
  	 correct in determining if contextToReturnTo is still married, and in case
  	 makeBaseFrameFor: cogs a method, which may cause a code compaction,
  	 in which case the frame must be free to avoid the relocation machinery
  	 tracing the dead frame.  Since freeing now temporarily violates the page-list
  	 ordering invariant, use the assert-free version."
  	stackPages freeStackPageNoAssert: stackPage.
  	isAContext := objectMemory isContext: contextToReturnTo.
  	(isAContext
  	 and: [self isStillMarriedContext: contextToReturnTo])
  		ifTrue:
  			[framePointer := self frameOfMarriedContext: contextToReturnTo.
  			 thePage := stackPages stackPageFor: framePointer.
  			 framePointer = thePage headFP
  				ifTrue:
  					[stackPointer := thePage headSP]
  				ifFalse:
  					["Returning to some interior frame, presumably because of a sender assignment.
  					  Move the frames above to another page (they may be in use, e.g. via coroutining).
  					  Make the interior frame the top frame."
  					 frameAbove := self findFrameAbove: framePointer inPage: thePage.
  					 "Since we've just deallocated a page we know that newStackPage won't deallocate an existing one."
  					 newPage := stackPages newStackPage.
  					 self assert: newPage = stackPage.
  					 self moveFramesIn: thePage through: frameAbove toPage: newPage.
  					 stackPages markStackPageMostRecentlyUsed: newPage.
  					 self setStackPointersFromPage: thePage]]
  		ifFalse:
  			[(isAContext
  			  and: [objectMemory isIntegerObject: (objectMemory fetchPointer: InstructionPointerIndex ofObject: contextToReturnTo)]) ifFalse:
  				[contextToReturnFrom := stackPages longAt: stackPage baseAddress - objectMemory wordSize.
  				 self tearDownAndRebuildFrameForCannotReturnBaseFrameReturnFrom: contextToReturnFrom
  					to: contextToReturnTo
  					returnValue: returnValue.
  				^self externalCannotReturn: returnValue from: contextToReturnFrom].
  			 "void the instructionPointer to stop it being incorrectly updated in a code
  			 compaction in makeBaseFrameFor:."
  			 instructionPointer := 0.
  			 thePage := self makeBaseFrameFor: contextToReturnTo.
  			 self setStackPointersFromPage: thePage].
  	self setStackPageAndLimit: thePage.
  	self assert: (stackPages stackPageFor: framePointer) = stackPage.
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self push: returnValue.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 "NOTREACHED"].
  	instructionPointer := self stackTop.
  	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  		[instructionPointer := self iframeSavedIP: framePointer].
  	self setMethod: (self iframeMethod: framePointer).
  	self stackTopPut: returnValue. "a.k.a. pop saved ip then push result"
  	self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: framePointer).
+ 	self invokeInterpreterFromMachineCode.
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  	"NOTREACHED"
  	^nil!

Item was added:
+ ----- Method: CoInterpreter>>ceEnterInterpreterOnReturnFromCogCode (in category 'trampolines') -----
+ ceEnterInterpreterOnReturnFromCogCode
+ 	"Perform a return from a machine code frame to an interpreted frame.
+ 	 The machine code has executed a return instruction when the return address
+ 	 is set to ceReturnToInterpreterPC.  Push the result and call interpret."
+ 	<api>
+ 	self assert: (objectMemory addressCouldBeOop: self stackTop).
+ 	self deny: (self isMachineCodeFrame: framePointer).
+ 	self setMethod: (self iframeMethod: framePointer).
+ 	instructionPointer := self iframeSavedIP: framePointer.
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
+ 	self invokeInterpreterFromMachineCode.
+ 	"NOTREACHED"
+ 	^nil!

Item was removed:
- ----- Method: CoInterpreter>>ceReturnToInterpreter: (in category 'trampolines') -----
- ceReturnToInterpreter: anOop
- 	"Perform a return from a machine code frame to an interpreted frame.
- 	 The machine code has executed a return instruction when the return address
- 	 is set to ceReturnToInterpreterPC.  Return the result and switch to the interpreter."
- 	<api>
- 	self assert: (objectMemory addressCouldBeOop: anOop).
- 	self flag: 'are you really sure setStackPageAndLimit: is needed?'.
- 	"I think you're only doing this for the markStackPageMostRecentlyUsed:
- 	 and that's probably not needed either"
- 	self setStackPageAndLimit: stackPage.
- 	self assert: (self isMachineCodeFrame: framePointer) not.
- 	self setMethod: (self iframeMethod: framePointer).
- 	self assertValidExecutionPointe: (self iframeSavedIP: framePointer)
- 		r: framePointer
- 		s: stackPointer
- 		imbar: true
- 		line: #'__LINE__'.
- 	instructionPointer := self iframeSavedIP: framePointer.
- 	self push: anOop.
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
- 	"NOTREACHED"
- 	^nil!

Item was changed:
  ----- Method: CoInterpreter>>ceSendMustBeBooleanTo:interpretingAtDelta: (in category 'trampolines') -----
  ceSendMustBeBooleanTo: aNonBooleanObject interpretingAtDelta: jumpSize
  	"For RegisterAllocatingCogit we want the pc following a conditional branch not to be reachable, so
  	 we don't have to generate code to reload registers.  But notionally the pc following a conditional
  	 branch is reached when continuing from a mustBeBoolean error.  Instead of supporting this in the
  	 JIT, simply convert to an interpreter frame, backup the pc to the branch, reenter the interpreter
  	 and hence retry the mustBeBoolean send therein.  N.B. We could do this for immutability violations
  	 too, but immutability is used in actual applications and so should be performant, whereas
  	 mustBeBoolean errors are extremely rare and so we choose brevity over performance in this case."
  	<api>
  	| cogMethod methodObj methodHeader startBcpc |
  	<var: 'cogMethod' type: #'CogBlockMethod *'>
  	<var: 'p' type: #'char *'>
  	self assert: (objectMemory addressCouldBeOop: aNonBooleanObject).
  	cogMethod := self mframeCogMethod: framePointer.
  	((self mframeIsBlockActivation: framePointer)
  	 and: [cogMethod cmIsFullBlock not])
  		ifTrue:
  			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
  			 startBcpc := cogMethod startpc]
  		ifFalse:
  			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
  			 startBcpc := self startPCOfMethod: methodObj].
  
  	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
  	instructionPointer := self popStack.
  	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
  	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - jumpSize - 1. "pre-decrement"
  
  	"Make space for the two extra fields in an interpreter frame"
  	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
  		[:p| | oop |
  		 oop := objectMemory longAt: p.
  		 objectMemory
  			longAt: p - objectMemory wordSize - objectMemory wordSize
  			put: (objectMemory longAt: p)].
  	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
  	self push: aNonBooleanObject.
  	"Fill in the fields"
  	objectMemory
  		longAt: framePointer + FoxIFrameFlags
  			put: (self
  					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
  					isBlock: (self mframeIsBlockActivation: framePointer)
  					numArgs: cogMethod cmNumArgs);
  		longAt: framePointer + FoxIFSavedIP
  			put: 0;
  		longAt: framePointer + FoxMethod
  			put: methodObj.
  
  	"and now reenter the interpreter..."
  	self setMethod: methodObj methodHeader: methodHeader.
+ 	self invokeInterpreterFromMachineCode.
+ 	"NOTREACHED"
+ 	^nil!
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.!

Item was changed:
  ----- Method: CoInterpreter>>flushMethodsWithMachineCodePrimitivesAndContinueAnswering: (in category 'primitive support') -----
  flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
  	"Arrange that any and all cog methods with machine code primitives can be and are discarded.
  	 Hence scan contexts and map their PCs to bytecode PCs if required, and scan frames, divorcing
  	 the frames of activationsif required.  The continue execution answering result.  THIS MUST BE
  	 INVOKED IN THE CONTEXT OF A PRIMITIVE.  It exists to support vmParameterAt:put:."
  	| activeContext theFrame thePage |
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self ensurePushedInstructionPointer.
  	self externalWriteBackHeadFramePointers.
  	self divorceMachineCodeFramesWithMachineCodePrimitiveMethod.
  	self ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs.
  	cogit unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: true.
  
  	"If flushing led to divorce continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		"pop bogus machine-code instructionPointer, arguments and receiver"
  		 self pop: argumentCount + 2 thenPush: result.
+ 		 cogit ceInvokeInterpret
- 		 self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  		 "NOTREACHED"].
  	"If not, work out where we are and continue"
  	theFrame := self frameOfMarriedContext: activeContext.
  	thePage := stackPages stackPageFor: theFrame.
  	self assert: thePage headFP = theFrame.
  	self setStackPageAndLimit: thePage.
  	self setStackPointersFromPage: thePage.
  	instructionPointer := self popStack.
  	 self pop: argumentCount + 1 thenPush: result!

Item was changed:
  ----- Method: CoInterpreter>>interpretMethodFromMachineCode (in category 'message sending') -----
  interpretMethodFromMachineCode
  	"Execute a method interpretively from machine code.  We assume (require) that newMethod
  	 messageSelector, primitiveFunctionPointer and argumentCount have been set in the caller.
  	 Once evaluated either continue in the interpreter via a jongjmp or in machine code via an
  	 enilopmart (a form of longjmp - a stinking rose by any other name)."
  	<inline: false>
  	cogit assertCStackWellAligned.
  	self assert: (self validInstructionPointer: instructionPointer inFrame: framePointer).
  	primitiveFunctionPointer ~= 0
  		ifTrue:
  			[primitiveFunctionPointer = #primitiveInvokeObjectAsMethod
  				ifTrue: [self assert: (objectMemory isOopCompiledMethod: newMethod) not]
  				ifFalse: [self assert: ((objectMemory isOopCompiledMethod: newMethod)
  									  and: [(self primitiveIndexOf: newMethod) ~= 0])].
  			 "Invoke an interpreter primitive (because the method is to be interpreted or has not yet been
  			  compiled).  This is very similar to invoking an interpreter primitive from a compiled primitive
  			  (see e.g. SimpleStackBasedCogit>>compileInterpreterPrimitive:).  Cut back the stack pointer
  			  (done above) to skip the return address and invoke the function.  On return if it has succeeded
  			  simply continue otherwise restore the stackPointer, collect the pc and interpret.  Note that
  			  frame building primitives such as primitiveClosureValue, primitiveEvaluateMethod et al will not
  			  return but will instead jump into either machine code or longjmp back to the interpreter."
  			"Assign stackPage headFP so we can tell if the primitive built a frame.  We can't simply save
  			 the framePointer since e.g. assignment to contexts (via primitiveInstVarAt:put:) can change the
  			 framePointer.  But context assignments will change both the framePointer and stackPage headFP."
  			
  			 self assert: (framePointer < stackPage baseAddress
  						and: [framePointer > (stackPage realStackLimit - (LargeContextSlots * objectMemory bytesPerOop / 2))]).
  			 stackPage headFP: framePointer.
  			 self isPrimitiveFunctionPointerAnIndex
  				ifTrue:
  					[self externalQuickPrimitiveResponse.
  					 primFailCode := 0]
  				ifFalse:
  					[self slowPrimitiveResponse].
  			self successful ifTrue:
  				[self return: self popStack toExecutive: false
  				 "NOTREACHED"]]
  		ifFalse:
  			[self assert: ((objectMemory isOopCompiledMethod: newMethod)
  						   and: [(self primitiveIndexOf: newMethod) = 0
  								or: [(self functionPointerFor: (self primitiveIndexOf: newMethod) inClass: objectMemory nilObject) = 0
  								or: [self isNullExternalPrimitiveCall: newMethod]]])].
  	"if not primitive, or primitive failed, activate the method and reenter the interpreter"
  	self activateNewMethod.
+ 	cogit ceInvokeInterpret.
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  	"NOTREACHED"
  	^nil!

Item was added:
+ ----- Method: CoInterpreter>>invokeInterpreterFromMachineCode (in category 'trampolines') -----
+ invokeInterpreterFromMachineCode
+ 	"This is just a rename for a send of interpret, but provides
+ 	 a simulation hook; see the CogVMSimulator subclass."
+ 	<inline: #always>
+ 	self interpret
+ 
+ 	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>return:toExecutive: (in category 'enilopmarts') -----
  return: returnValue toExecutive: inInterpreter
  	"We have made a context switch, either when interpreting or from machine code.
  	 Effectively return to the current frame, either by entering machine code, or
  	 longjmp-ing back to the interpreter or simply returning, depending on where we are."
  
  	cogit assertCStackWellAligned.
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  		 self push: instructionPointer.
  		 self push: returnValue.
  		 cogit ceEnterCogCodePopReceiverReg
  		 "NOTREACHED"].
  	self push: returnValue.
  	self setMethod: (self iframeMethod: framePointer).
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  		[instructionPointer := self iframeSavedIP: framePointer].
  	inInterpreter ifTrue:
  		[^nil].
+ 	cogit ceInvokeInterpret.
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: CoInterpreter>>returnToExecutive:postContextSwitch: (in category 'enilopmarts') -----
  returnToExecutive: inInterpreter postContextSwitch: switchedContext
  	"Return to the current frame, either by entering machine code, or longjmp-ing back to the
  	 interpreter or simply returning, depending on where we are. To know whether to return or
  	 enter machine code we have to know from whence we came.  We could have come from
  	 the interpreter, either directly or via a machine code primitive.  We could have come from
  	 machine code.  The instructionPointer tells us where from.  If it is above startOfMemory we're
  	 in the interpreter.  If it is below, then we are in machine-code unless it is ceReturnToInterpreterPC,
  	 in which case we're in a machine-code primitive called from the interpreter."
  	<inline: false>
  	| cogMethod retValue fullyInInterpreter |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  
  	cogit assertCStackWellAligned.
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  		 "If returning after a context switch then a result may have to be popped from the stack.
  		  If the process is suspended at a send then the result of the primitive in which the
  		  process was suspended is still on the stack and must be popped into ReceiverResultReg.
  		  If not, nothing should be popped and ReceiverResultReg gets the receiver."
  		 switchedContext
  			ifTrue:
  				[cogMethod := self mframeCogMethod: framePointer.
  				self assert: (instructionPointer > cogit minCogMethodAddress 
  							and: [instructionPointer < cogit maxCogMethodAddress]).
  				 (instructionPointer ~= (cogMethod asInteger + cogMethod stackCheckOffset)
  				  and: [cogit isSendReturnPC: instructionPointer])
  					ifTrue:
  						[self assert: (objectMemory addressCouldBeOop: self stackTop).
  						 retValue := self popStack]
  					ifFalse:
  						[retValue := self mframeReceiver: framePointer]]
  			ifFalse: [retValue := self mframeReceiver: framePointer].
  		 self push: instructionPointer.
  		 self push: retValue.
  		 cogit ceEnterCogCodePopReceiverReg
  		 "NOTREACHED"].
  	self setMethod: (self iframeMethod: framePointer).
  	fullyInInterpreter := inInterpreter.
  	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  		[instructionPointer := (self iframeSavedIP: framePointer) asUnsignedInteger.
  		 fullyInInterpreter := false].
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	fullyInInterpreter ifFalse:
+ 		[cogit ceInvokeInterpret
- 		[self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  		 "NOTREACHED"].
  	^nil!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveLongRunningPrimitiveSemaphore (in category 'process primitives') -----
  primitiveLongRunningPrimitiveSemaphore
  	"Primitive. Install the semaphore to be used for collecting long-running primitives, 
  	 or nil if no semaphore should be used."
  	| sema flushState activeContext |
  	<export: true>
  	self methodArgumentCount ~= 1 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	sema := self stackValue: 0.
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := longRunningPrimitiveCheckSemaphore notNil.
  			 longRunningPrimitiveCheckSemaphore := nil]
  		ifFalse:
  			[flushState := longRunningPrimitiveCheckSemaphore isNil.
  			 (objectMemory isSemaphoreOop: sema) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument].
  			 longRunningPrimitiveCheckSemaphore := sema].
  	"If we've switched checking on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop setting
  	 newMethod in machine code primitive invocations, and so generate
  	 slightly different code from here on in."
  	flushState ifTrue:
  		[self push: instructionPointer.
  		 activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self assert: (((self stackValue: 0) = objectMemory nilObject and: [longRunningPrimitiveCheckSemaphore isNil])
  				  or: [(self stackValue: 0) = longRunningPrimitiveCheckSemaphore
  					  and: [objectMemory isSemaphoreOop: sema]])].
  	self voidLongRunningPrimitive: 'install'.
  	self pop: 1.
  	flushState ifTrue:
+ 		[cogit ceInvokeInterpret]!
- 		[self siglong: reenterInterpreter jmp: ReturnToInterpreter]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveProfileSemaphore (in category 'process primitives') -----
  primitiveProfileSemaphore
  	"Primitive. Install the semaphore to be used for profiling, 
  	or nil if no semaphore should be used.
  	See also primitiveProfileStart."
  	| sema flushState activeContext |
  	<export: true>
  	self methodArgumentCount ~= 1 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	sema := self stackValue: 0.
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := profileSemaphore ~= objectMemory nilObject]
  		ifFalse:
  			[flushState := profileSemaphore = objectMemory nilObject.
  			 (objectMemory isSemaphoreOop: sema) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument]].
  	profileSemaphore := sema.
  	"If we've switched profiling on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop
  	 testing the profile clock in machine code primitive invocations,
  	 and so generate slightly different code from here on in."
  	flushState ifTrue:
  		[self push: instructionPointer.
  		 activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self assert: (((self stackValue: 0) = objectMemory nilObject and: [profileSemaphore = objectMemory nilObject])
  				  or: [(self stackValue: 0) = profileSemaphore
  					  and: [objectMemory isSemaphoreOop: sema]])].
  	profileProcess := profileMethod := objectMemory nilObject.
  	self pop: 1.
  	flushState ifTrue:
+ 		[cogit ceInvokeInterpret]!
- 		[self siglong: reenterInterpreter jmp: ReturnToInterpreter]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveSnapshot (in category 'system control primitives') -----
  primitiveSnapshot
  	"Save a normal snapshot under the same name as it was loaded
  	 unless it has been renamed by the last primitiveImageName.
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	<inline: false>
  	self snapshot: false.
  	(self iframeMethod: framePointer) = newMethod ifTrue:
  		["snapshot: has reached the end and built a frame.
  		 In the JIT we need to back-up the pc before reentering the interpreter."
  		instructionPointer := instructionPointer - 1].
+ 	cogit ceInvokeInterpret
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveSnapshotEmbedded (in category 'system control primitives') -----
  primitiveSnapshotEmbedded
  	"Save an embedded snapshot.
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	<inline: false>
  	self snapshot: true.
  	(self iframeMethod: framePointer) = newMethod ifTrue:
  		["snapshot: has reached the end and built a frame.
  		 In the JIT we need to back-up the pc before reentering the interpreter."
  		instructionPointer := instructionPointer - 1].
+ 	cogit ceInvokeInterpret
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveVoidVMState (in category 'system control primitives') -----
  primitiveVoidVMState
  	"Void all internal VM state in the stack and machine code zones
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	| activeContext |
  	self push: instructionPointer.
  	activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
+ 	cogit ceInvokeInterpret
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveVoidVMStateForMethod (in category 'system control primitives') -----
  primitiveVoidVMStateForMethod
  	"The receiver (or first argument) must be a compiledMethod.  The optional (or second) argument must be a
  	 boolean. Clear all VM state associated with the method, including any machine code, or machine code pcs
  	 in context objects.  If the optional boolean argument is false do not scan the heap looking for contexts."
  	| activeContext methodObj scanHeapForContexts hasCogMethod theFrame thePage |
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	scanHeapForContexts := true. "See comment ''One might think...'' below"
  	"In Smalltalk allow both aMethod voidCogVMState and aMethod voidCogVMStateScanningContextsIf: aBoolean"
  	argumentCount = 0
  		ifTrue:
  			[methodObj := self stackTop]
  		ifFalse:
  			[methodObj := self stackValue: 1.
  			 scanHeapForContexts := self booleanValueOf: self stackTop.
  			 self failed ifTrue:
  				[^self primitiveFailFor: PrimErrBadArgument]].
  	NewspeakVM
  		ifFalse:
  			[argumentCount > 1 ifTrue:
  				[^self primitiveFailFor: PrimErrBadNumArgs]]
  		 ifTrue: "In the NewspeakVM we allow VMMirror voidStateFor: method scanningIf: aBoolean as well as the Smalltalk forms."
  			[argumentCount >= 2 ifTrue:
  				[argumentCount > 2 ifTrue:
  					[^self primitiveFailFor: PrimErrBadNumArgs].
  				 (objectMemory isOopCompiledMethod: methodObj) ifFalse:
  					[^self primitiveFailFor: PrimErrBadArgument]]].
  	self flushMethodCacheForMethod: methodObj.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self ensurePushedInstructionPointer.
  	self externalWriteBackHeadFramePointers.
  	(hasCogMethod := self methodHasCogMethod: methodObj) ifTrue:
  		[self divorceMachineCodeFramesWithMethod: methodObj].
  	"One might think (as this author did) that the heap scan is unnecessary if the method does not
  	 have a cog method.  But it could be the case that the code zone has recently been reclaimed
  	 and so not having a cog method is no indication that it didn't have a cog method some time in
  	 the recent past, and that there are indeed still contexts with machine code pcs out there.  The
  	 only steps that can be avoided are divorcing frames in the stack zone, and scanning to unlink and
  	 free if there isn't a cog method, unless we are told otherwise."
  	scanHeapForContexts ifTrue:
  		[self ensureAllContextsWithMethodHaveBytecodePCs: methodObj].
  	hasCogMethod ifTrue:
  		[cogit unlinkSendsTo: methodObj andFreeIf: true].
  
  	"If flushing led to divorce continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self popStack. "pop bogus machine-code instructionPointer"
  		 self assert: (methodObj = self stackTop or: [argumentCount > 0 and: [methodObj = (self stackValue: 1)]]).
  		 self pop: argumentCount.
+ 		 cogit ceInvokeInterpret
- 		 self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  		 "NOTREACHED"].
  	"If not, work out where we are and continue"
  	theFrame := self frameOfMarriedContext: activeContext.
  	thePage := stackPages stackPageFor: theFrame.
  	self assert: thePage headFP = theFrame.
  	self setStackPageAndLimit: thePage.
  	self setStackPointersFromPage: thePage.
  	instructionPointer := self popStack.
  	self assert: (methodObj = self stackTop or: [argumentCount > 0 and: [methodObj = (self stackValue: 1)]]).
  	self pop: argumentCount!

Item was added:
+ ----- Method: CogVMSimulator>>invokeInterpreterFromMachineCode (in category 'trampolines') -----
+ invokeInterpreterFromMachineCode
+ 	"In simulation we raise an exception to unwind the stack and get back to the current level of interpret execution."
+ 	reenterInterpreter
+ 		returnValue: ReturnToInterpreter;
+ 		signal
+ 
+ 	"NOTREACHED"!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| backEnd |
  	backEnd := CogCompilerClass basicNew.
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetFP
  			declareC: 'usqIntptr_t (*ceGetFP)(void)';
  		var: #ceGetSP
  			declareC: 'usqIntptr_t (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
+ 		var: #ceInvokeInterpret
+ 			declareC: 'void (*ceInvokeInterpret)(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: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	
  	aCCodeGenerator
  		var: #ceTryLockVMOwner
  			declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)\#endif /* COGMTVM */'.
  
  	backEnd numCheckLZCNTOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckLZCNTFunction
  				declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)'].
  	backEnd numCheckFeaturesOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckFeaturesFunction
  				declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)'].
  	backEnd numICacheFlushOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceFlushICache
  				declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)'].
  	aCCodeGenerator
  		var: #ceFlushDCache
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif';
  		var: #codeToDataDelta
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static sqInt codeToDataDelta\#else\# define codeToDataDelta 0\#endif'.
  
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					fullBlockNoContextSwitchEntry fullBlockEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #cPICPrototype type: #'CogMethod *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *';
  		declareVar: #methodZoneBase type: #usqInt.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'.
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[aCCodeGenerator
  			var: #directedSuperSendTrampolines
  				declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  			var: #directedSuperBindingSendTrampolines
  				declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]'].
  	NewspeakVM ifTrue:
  		[aCCodeGenerator
  			var: #selfSendTrampolines
  				declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  			var: #dynamicSuperSendTrampolines
  				declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  			var: #implicitReceiverSendTrampolines
  				declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  			var: #outerSendTrampolines
  				declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]'].
  	aCCodeGenerator
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #minValidCallAddress type: #'usqIntptr_t'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltalk 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'.
  	self declareFlagVarsAsByteIn: aCCodeGenerator!

Item was changed:
  ----- Method: Cogit class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are
  	 accessed from VM support code."
+ 	^#('ceBaseFrameReturnTrampoline' ceCaptureCStackPointers 'ceCheckForInterruptTrampoline'
- 	^#('ceBaseFrameReturnTrampoline' 'ceCaptureCStackPointers' 'ceCheckForInterruptTrampoline'
  		ceEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverReg
  		ceCallCogCodePopReceiverReg realCECallCogCodePopReceiverReg
  		ceCallCogCodePopReceiverAndClassRegs realCECallCogCodePopReceiverAndClassRegs
+ 		ceInvokeInterpret 'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
- 		'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
  		ceTryLockVMOwner ceUnlockVMOwner
  		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'cmSelfSendEntryOffset'
  		'missOffset' 'cbEntryOffset' 'cbNoSwitchEntryOffset' 'blockNoContextSwitchOffset' breakPC
  		ceGetFP ceGetSP cFramePointerInUse
  		traceFlags traceStores)
  			includes: var!

Item was changed:
  ----- Method: Cogit class>>numTrampolines (in category 'trampoline support') -----
  numTrampolines
+ 	^37 "29 + 4 each for self and super sends" + (LowcodeVM ifTrue: [3] ifFalse: [0]) + CogCompilerClass numTrampolines
- 	^38 "30 + 4 each for self and super sends" + (LowcodeVM ifTrue: [1] ifFalse: [0]) + CogCompilerClass numTrampolines
  
  	"self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"!

Item was added:
+ ----- Method: Cogit>>ceInvokeInterpret (in category 'simulation only') -----
+ ceInvokeInterpret
+ 	<api: 'extern void (*ceInvokeInterpret)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceInvokeInterpret numArgs: 1!

Item was added:
+ ----- Method: Cogit>>genInvokeInterpretTrampoline (in category 'initialization') -----
+ genInvokeInterpretTrampoline
+ 	"Switch to the C stack (do *not* save the Smalltalk stack pointers;
+ 	 this is the caller's responsibility), and invoke interpret PDQ."
+ 	| startAddress |
+ 	<inline: false>
+ 	startAddress := methodZoneBase.
+ 	self zeroOpcodeIndex.
+ 	cFramePointerInUse
+ 		ifTrue: [backEnd genLoadCStackPointers]
+ 		ifFalse: [backEnd genLoadCStackPointer].
+ 	self
+ 		compileCallFor: #interpret
+ 		numArgs: 0 arg: nil arg: nil arg: nil arg: nil
+ 		resultReg: NoReg
+ 		regsToSave: self emptyRegisterMask.
+ 	self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	self recordGeneratedRunTime: 'ceInvokeInterpret' address: startAddress.
+ 	^startAddress!

Item was added:
+ ----- Method: Cogit>>genReturnToInterpreterTrampoline (in category 'initialization') -----
+ genReturnToInterpreterTrampoline
+ 	self zeroOpcodeIndex.
+ 	"Set the instruction pointer to the interpreter frame's saved ip, set the method and the bytecode set offset,
+ 	 then call interpret."
+ 	self PushR: ReceiverResultReg. "The result"
+ 	^self genTrampolineFor: #ceEnterInterpreterOnReturnFromCogCode
+ 		called: 'ceEnterInterpreterOnReturnFromCogCode'
+ 		numArgs: 0 arg: nil arg: nil arg: nil arg: nil
+ 		regsToSave: self emptyRegisterMask
+ 		pushLinkReg: false
+ 		resultReg: NoReg
+ 		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>generateRunTimeTrampolines (in category 'initialization') -----
  generateRunTimeTrampolines
  	"Generate the run-time entries at the base of the native code zone and update the base."
  	
  	ceSendMustBeBooleanAddFalseTrampoline := self genMustBeBooleanTrampolineFor: objectMemory falseObject
  														called: 'ceSendMustBeBooleanAddFalseTrampoline'.
  	ceSendMustBeBooleanAddTrueTrampoline := self genMustBeBooleanTrampolineFor: objectMemory trueObject
  														called: 'ceSendMustBeBooleanAddTrueTrampoline'.
  	ceNonLocalReturnTrampoline := self genNonLocalReturnTrampoline.
  	ceCheckForInterruptTrampoline := self genCheckForInterruptsTrampoline.
  	"Neither of the context inst var access trampolines save registers.  Their operation could cause
  	 arbitrary update of stack frames, so the assumption is that callers flush the stack before calling
  	 the context inst var access trampolines, and that everything except the result is dead afterwards."
  	ceFetchContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:
  											called: 'ceFetchContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											result: SendNumArgsReg.
  	ceStoreContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:value:
  											called: 'ceStoreContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											arg: ClassReg
  											result: ReceiverResultReg. "to keep ReceiverResultReg live.".
  	ceCannotResumeTrampoline := self genTrampolineFor: #ceCannotResume
  											called: 'ceCannotResumeTrampoline'.
+ 	"ceInvokeInterpreter is an optimization and a work-around. Historically we used setjmp/longjmp to reenter the
+ 	 interpreter at the current C stack base.  The C stack base is set at start-up and on each callback enter and
+ 	 callback return. The interpreter must be invoked whenever a non-machine-code method must be run.  That might
+ 	 be when invoking an interpreter method from one of the send linking routines (ceSend:...), or on continuing from
+ 	 an evaluation primitive such as primitiveExecuteMethod.  The problem here is that such primitives could have
+ 	 been invoked by the interpreter or by machine code.  So some form of non-local jump is required. But at least as
+ 	 early as MSVC Community 2017, the Microshaft longjmp performs stack unwinding which gets hoplessly confused
+ 	 (bless its little heart) by any stack switch between machine code and C stack, and raises a spurious
+ 		Stack cookie instrumentation code detected a stack-based buffer overrun
+ 	 error from the bowels of gs_report.c _GSHandlerCheck.
+ 	 Since the CoInterpreter maintains the base of the C stack in CFramePointer & CStackPointer, it is straight-forward
+ 	 for us to simply call interpret after doing the switch to the C stack, avoiding the stack unwind issue altogether."
+ 	ceInvokeInterpret := self genInvokeInterpretTrampoline.
  	"These two are unusual; they are reached by return instructions."
+ 	ceReturnToInterpreterTrampoline := self genReturnToInterpreterTrampoline.
  	ceBaseFrameReturnTrampoline := self genReturnTrampolineFor: #ceBaseFrameReturn:
  											called: 'ceBaseFrameReturnTrampoline'
  											arg: ReceiverResultReg.
+ 	LowcodeVM ifTrue:
+ 		[ceFFICalloutTrampoline := self genFFICalloutTrampoline.
+ 		 ceMallocTrampoline := self genTrampolineFor: #ceMalloc:
+ 									called: 'ceMallocTrampoline'
+ 									arg: ReceiverResultReg
+ 									result: TempReg.
+ 		 ceFreeTrampoline := self genTrampolineFor: #ceFree:
+ 									called: 'ceFreeTrampoline'
+ 									arg: ReceiverResultReg]!
- 	ceReturnToInterpreterTrampoline := self
- 											genReturnTrampolineFor: #ceReturnToInterpreter:
- 											called: 'ceReturnToInterpreterTrampoline'
- 											arg: ReceiverResultReg.
- 	ceMallocTrampoline := self genTrampolineFor: #ceMalloc:
- 											called: 'ceMallocTrampoline'
- 											arg: ReceiverResultReg
- 											result: TempReg.
- 	ceFreeTrampoline := self genTrampolineFor: #ceFree:
- 											called: 'ceFreeTrampoline'
- 											arg: ReceiverResultReg.
- 	LowcodeVM ifTrue: [
- 		ceFFICalloutTrampoline := self genFFICalloutTrampoline.
- 	]!




More information about the Vm-dev mailing list