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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 1 21:54:08 UTC 2020


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

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

Name: VMMaker.oscog-eem.2737
Author: eem
Time: 1 April 2020, 2:53:51.882349 pm
UUID: ca691460-8bf3-48df-91dd-3132219b7bc4
Ancestors: VMMaker.oscog-eem.2736

CoInterpreter: Improve on the new simpler invoke interpeeter scheme by including the releant return address so that the C stack looks prop[erly connected after reentering interpret.  This depends on getReturnAddress being defined in C.  Both GCC (and those that support its builtins such as clang and ICC) and MSVC provide builtins/intrinsics for accessing the retrn address, so we don't bother to implement it in the Cogit.

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

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
+ 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer CReturnAddress'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
+ !CoInterpreter commentStamp: 'eem 3/31/2020 18:56' prior: 0!
- !CoInterpreter commentStamp: 'eem 10/10/2019 09:08' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
  	- the names associated with the codes of events in traceLog
  
  CFramePointer
  	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CStackPointer
+ 	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
+ 
+ CReturnAddress
+ 	- the return address for the function call which invoked the interpreter at start-up.  Using this as teh return address when entering the interpreter via ceInvokeInterpeter maintains a valid stack.  Since this is effevtively a constant it does not need to be saved and restored once set.!
- 	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.!

Item was changed:
  ----- Method: CoInterpreter class>>clusteredVariableNames (in category 'translation') -----
  clusteredVariableNames
  	"Insist that these variables are present early in the list of variables, and in this order,
  	 so that e.g. they are conveniently accessed via the VarBaseReg if it is available."
+ 	^#(stackPointer framePointer CStackPointer CFramePointer CReturnAddress
- 	^#(stackPointer framePointer CStackPointer CFramePointer
  		stackLimit scavengeThreshold freeStart needGCFlag specialObjectsOop
  		primFailCode newMethod instructionPointer argumentCount nextProfileTick
  		nativeSP nativeStackPointer shadowCallStackPointer)!

Item was changed:
  ----- Method: CoInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Override to avoid repeating StackInterpreter's declarations and add our own extensions"
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	aCCodeGenerator
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile: (aCCodeGenerator vmClass isThreadedVM 
  			ifTrue: ['"cointerpmt.h"'] 
  			ifFalse: ['"cointerp.h"']);
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator vmClass
  		declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: aCCodeGenerator interpreterVersion.
  	aCCodeGenerator
  		var: #heapBase type: #usqInt;
  		var: #statCodeCompactionUsecs type: #usqLong;
  		var: #maxLiteralCountForCompile
  			declareC: 'sqInt maxLiteralCountForCompile = MaxLiteralCountForCompile /* ', MaxLiteralCountForCompile printString, ' */';
  		var: #minBackwardJumpCountForCompile
  			declareC: 'sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* ', MinBackwardJumpCountForCompile printString, ' */'.
  	aCCodeGenerator
  		removeVariable: 'atCache'; "Way too much trouble than it's worth in the Cog VM"
  		removeVariable: 'reenterInterpreter'. "We can use the JIT and CFrame/StrackPointer for a lighter-weight solution."
  	aCCodeGenerator
  		var: #primTraceLogIndex type: #'unsigned char';
  		var: #primTraceLog declareC: 'sqInt primTraceLog[256]';
  		var: #traceLog
  		declareC: 'sqInt traceLog[TraceBufferSize /* ', TraceBufferSize printString, ' */]';
  		var: #traceSources type: #'char *' array: TraceSources.
  	aCCodeGenerator
  		var: #CFramePointer type: #'volatile usqIntptr_t';
+ 		var: #CStackPointer type: #'volatile usqIntptr_t';
+ 		var: #CReturnAddress type: #'volatile usqIntptr_t'!
- 		var: #CStackPointer type: #'volatile usqIntptr_t'!

Item was added:
+ ----- Method: CoInterpreter>>cReturnAddressAddress (in category 'trampoline support') -----
+ cReturnAddressAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self
+ 		cCode: [(self addressOf: CReturnAddress) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getCReturnAddress in: self]!

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).
+ 	cogit ceInvokeInterpret.
- 	self invokeInterpreterFromMachineCode.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- 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__'.
+ 	cogit ceInvokeInterpret.
- 	self invokeInterpreterFromMachineCode.
  	"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.
+ 	cogit ceInvokeInterpret.
- 	self invokeInterpreterFromMachineCode.
  	"NOTREACHED"
  	^nil!

Item was added:
+ ----- Method: CoInterpreter>>getCReturnAddress (in category 'simulation only') -----
+ getCReturnAddress
+ 	<doNotGenerate>
+ 	self assert: CReturnAddress isSymbol.
+ 	^cogit simulatedAddressFor: CReturnAddress!

Item was added:
+ ----- Method: CoInterpreter>>interpret (in category 'interpreter shell') -----
+ interpret
+ 	"This is the main interpreter loop.
+ 	 In a pure interpreter it loops forever, fetching and executing bytecodes.
+ 	 With the Cogit JIT executing code as well, the interpreter is reentered from machine code
+ 	 whenever the machine code wants to interpret a method instead of executing its machine
+ 	 code.  Entry into the interpreter is done via a ''jump call'' in machine code that uses
+ 	 CFramePointer and CStackPointer to find the base of the C stack (set in CoInterpreter>>
+ 	 enterSmalltalkExecutiveImplementation) and substitutes CReturnAddress as the return
+ 	 address in the code so it always appears that interpret has been called from
+ 	 CoInterpreter>>enterSmalltalkExecutiveImplementation, which may be important to,
+ 	 for example, C exception handling inside the VM.
+ 
+ 	 When running in the context of a browser plugin VM the interpreter must return control
+ 	 to the browser periodically. This should done only when the state of the currently running
+ 	 Squeak thread is safely stored in the object heap. Since this is the case at the moment
+ 	 that a check for interrupts is performed, that is when we return to the browser if it is time
+ 	 to do so. Interrupt checks happen quite frequently."
+ 
+ 	<inline: false>
+ 	"If stacklimit is zero then the stack pages have not been initialized."
+ 	stackLimit = 0 ifTrue:
+ 		[^self initStackPagesAndInterpret].
+ 	CReturnAddress ifNil:
+ 		[CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t].
+ 	"record entry time when running as a browser plug-in"
+ 	self browserPluginInitialiseIfNeeded.
+ 	self internalizeIPandSP.
+ 	self initExtensions.
+ 	self fetchNextBytecode.
+ 	[true] whileTrue: [self dispatchOn: currentBytecode in: BytecodeTable].
+ 	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
+ 	self externalizeIPandSP.
+ 	^nil!

Item was removed:
- ----- 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>
- 	cogit ceInvokeInterpret
- 
- 	"NOTREACHED"!

Item was added:
+ ----- Method: CogARMCompiler>>genSubstituteReturnAddressR: (in category 'abstract instructions') -----
+ genSubstituteReturnAddressR: retpcReg
+ 	<inline: true>
+ 	^cogit MoveR: retpcReg R: LR!

Item was added:
+ ----- Method: CogIA32Compiler>>genSubstituteReturnAddressR: (in category 'abstract instructions') -----
+ genSubstituteReturnAddressR: retpcReg
+ 	<inline: true>
+ 	^cogit PushR: retpcReg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genSubstituteReturnAddressR: (in category 'abstract instructions') -----
+ genSubstituteReturnAddressR: retpcReg
+ 	<inline: true>
+ 	^cogit MoveR: retpcReg R: RA!

Item was added:
+ ----- Method: CogVMSimulator>>getReturnAddress (in category 'simulation only') -----
+ getReturnAddress
+ 	^(thisContext findContextSuchThat: [:ctxt| ctxt selector == #interpret]) sender method selector!

Item was changed:
  ----- Method: CogVMSimulator>>interpret (in category 'interpreter shell') -----
  interpret
  	"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes.
  	 When running in the context of a web browser plugin VM, however, it must return control to the
  	 web browser periodically. This should done only when the state of the currently running Squeak
  	 thread is safely stored in the object heap. Since this is the case at the moment that a check for
  	 interrupts is performed, that is when we return to the browser if it is time to do so.  Interrupt
  	 checks happen quite frequently.
  
  	Override for simulation to insert bytecode breakpoint support."
  
  	"If stacklimit is zero then the stack pages have not been initialized."
  	stackLimit = 0 ifTrue:
  		[^self initStackPagesAndInterpret].
+ 	CReturnAddress ifNil:
+ 		[CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t].
  	self useCogitBreakBlockIfNone.
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
  	self internalizeIPandSP.
  	self initExtensions.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 atEachStepBlock value. "N.B. may be nil"
  		 self dispatchOn: currentBytecode in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
  	^nil
  !

Item was removed:
- ----- 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 added:
+ ----- Method: CogVMSimulator>>reenterInterpreter (in category 'simulation only') -----
+ reenterInterpreter
+ 	ReenterInterpreter new
+ 		returnValue: ReturnToInterpreter;
+ 		signal!

Item was added:
+ ----- Method: CogX64Compiler>>genSubstituteReturnAddressR: (in category 'abstract instructions') -----
+ genSubstituteReturnAddressR: retpcReg
+ 	<inline: true>
+ 	^cogit PushR: retpcReg!

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

Item was changed:
  ----- 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.
  	backEnd hasVarBaseRegister ifTrue:
  		[self MoveCq: self varBaseAddress R: VarBaseReg]. "Must happen first; value may be used in genLoadStackPointers"
  	cFramePointerInUse
  		ifTrue: [backEnd genLoadCStackPointers]
  		ifFalse: [backEnd genLoadCStackPointer].
+ 	"Sideways call interpret so that the stack looks correct, for exception handling etc"
+ 	backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self MoveAw: coInterpreter cReturnAddressAddress R: LinkReg]
+ 		ifFalse:
+ 			[self MoveAw: coInterpreter cReturnAddressAddress R: ABIResultReg.
+ 			 backEnd genSubstituteReturnAddressR: ABIResultReg].
+ 	self JumpFullRT: (self
+ 						cCode: [#interpret asUnsignedInteger]
+ 						inSmalltalk: [self simulatedTrampolineFor: #interpret]).
- 	self CallFullRT: #interpret registersToBeSavedMask: self emptyRegisterMask.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: 'ceInvokeInterpret' address: startAddress.
  	^startAddress!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf retpc |
  	evaluable := simulatedTrampolines
  					at: aProcessorSimulationTrap address
  					ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  								in: simulatedTrampolines].
  	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].
  	(backEnd wantsNearAddressFor: function) ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	memory := coInterpreter memory.
  	aProcessorSimulationTrap type == #call
  		ifTrue:
  			[(leaf := coInterpreter mcprims includes: function)
  				ifTrue:
  					[processor
  						simulateLeafCallOf: aProcessorSimulationTrap address
  						nextpc: aProcessorSimulationTrap nextpc
  						memory: memory.
  					 retpc := processor leafRetpcIn: memory]
  				ifFalse:
  					[processor
  						simulateCallOf: aProcessorSimulationTrap address
  						nextpc: aProcessorSimulationTrap nextpc
  						memory: memory.
  					 retpc := processor retpcIn: memory].
  			 self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[leaf := false.
  			 processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
  				memory: memory.
  			 retpc := processor retpcIn: memory. "sideways call; the primitive has pushed a return address."
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
+ 	function == #interpret ifTrue: "i.e. we're here via ceInvokeInterpret and should discard all state back to enterSmalltalkExecutiveImplementation"
+ 		[coInterpreter reenterInterpreter].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   clickConfirm ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: 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 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:
  						["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  						 (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) 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: memory. ')'}.
  		 leaf
  			ifTrue: [processor simulateLeafReturnIn: memory]
  			ifFalse: [processor simulateReturnIn: memory].
  		 self assert: processor pc = retpc.
  		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: 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: Cogit>>simulateEnilopmart:numArgs: (in category 'simulation only') -----
  simulateEnilopmart: enilopmartAddress numArgs: n
  	<doNotGenerate>
  	"Enter Cog code, popping the class reg and receiver from the stack
  	 and then returning to the address beneath them.
  	 In the actual VM the enilopmart is a function pointer and so senders
  	 of this method end up calling the enilopmart to enter machine code.
  	 In simulation we either need to start simulating execution (if we're in
  	 the interpreter) or return to the simulation (if we're in the run-time
  	 called from machine code. We should also smash the register state
  	 since, being an abnormal entry, no saved registers will be restored."
  	self assert: (coInterpreter isOnRumpCStack: processor sp).
+ 	self assert: (n = 0 or: [(coInterpreter stackValue: n) between: guardPageSize and: methodZone freeStart - 1]).
- 	self assert: ((coInterpreter stackValue: n) between: guardPageSize and: methodZone freeStart - 1).
  	(printInstructions or: [printRegisters]) ifTrue:
  		[coInterpreter printExternalHeadFrame].
  	processor
  		smashRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  		simulateLeafCallOf: enilopmartAddress
  		nextpc: 16rBADF00D
  		memory: coInterpreter memory.
  	"If we're already simulating in the context of machine code then
  	 this will take us back to handleCallSimulationTrap:.  Otherwise
  	 start executing machine code in the simulator."
  	(ReenterMachineCode new returnValue: #continueNoReturn) signal.
  	self simulateCogCodeAt: enilopmartAddress.
  	"We should either longjmp back to the interpreter or
  	 stay in machine code so control should not reach here."
  	self assert: false!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>getCReturnAddress (in category 'accessing') -----
+ getCReturnAddress
+ 	^coInterpreter getCReturnAddress!



More information about the Vm-dev mailing list