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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 23 19:32:29 UTC 2018


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

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

Name: VMMaker.oscog-eem.2431
Author: eem
Time: 23 August 2018, 12:31:54.020173 pm
UUID: 2771de4d-ef66-4fd5-ab42-bbb4709819ec
Ancestors: VMMaker.oscog-eem.2430

Core VM:
Kernel of support for failing FFI calls that raise exceptions.  This provides simulation support for catching the signal and activating the invoking method as a primitive failure.  The platform exception handlers still need of course to be modified to invoke this support.

Refactoring:
Move reenterInterpreter up to StackInterpreter from CoInterpreter, along with all relevant methods.  Add mustBeInterpreterFrame agument to justActivateNewMethod: to that the Cog VM can insist on activating the failing FFI invoking method in the interpreter, which simplifies the machinery in activateFailingPrimitiveMethod, which is the api entry-point that does the work of failing the primitive and long-jumping to the interpreter.  Fix a bug in CoInterpreter's justActivateNewMethod: which left the instructionPointer one ahead if activating a faiiing primitive method.  Add primitiveFailForFFIException:at: as a setter for the exception state.

Add PrimErrFFIException.  Update cloneOSErrorObj:numSlots: to deal with a three slot subclass of PrimitiveError that adds a pc at which an exception took place (exception can be represented by errorCode).

Plugins:
Have the ThreadedFFIPlugin create a valid stack allocation so it can simulate a callout.  Have its dispatchFunctionPointer:[with:*] methods catch MessageNotUnderstood and invoke primitiveFailForFFIException:at: and then activateFailingPrimitiveMethod.  Update morphIntoConcreteSubclass: to run any relevant class initialization if required.

Misc:
Initializing extensions should occur before fetching a bytecode, in case the bytecode is itself extended.

Add the 5 & 6 argument perform: methopds to this package, instead of relying on a file-in that ends up causing me to accidentally commit them to Kernel.

Have attemptToComputeTempNamesFor: use newFrom: instead of withAll: to work in Pharo.  Hopefully temporary.

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

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'
+ 	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'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod reenterInterpreter deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile'
- 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize ReturnToInterpreter 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 12/7/2017 11:19' 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!

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"
- 	aCCodeGenerator removeVariable: 'atCache'.
  	aCCodeGenerator
- 		var: #reenterInterpreter
- 		declareC: 'jmp_buf reenterInterpreter; /* private export */'.
- 	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!

Item was changed:
  ----- Method: CoInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	COGVM := true.
  
  	MinBackwardJumpCountForCompile := 40.
  
  	MaxNumArgs := 15.
  	PrimCallNeedsNewMethod := 1.
  	PrimCallNeedsPrimitiveFunction := 2.
  	PrimCallMayCallBack := 4.
  	PrimCallOnSmalltalkStack := 8.
  	PrimCallCollectsProfileSamples := 16.
  	CheckAllocationFillerAfterPrimCall := 32.
  	PrimCallDoNotJIT := 64.
  
- 	ReturnToInterpreter := 1. "setjmp/longjmp code."
- 
  	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
  	TraceBufferSize := 256 * 3. "Room for 256 events"
  	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
  	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
  	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
  	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
  	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
  	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
  	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
  	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
  	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
  	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
  	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
  	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
  	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
  	TracePrimitiveFailure := self objectMemoryClass basicNew integerObjectOf: 14.
  	TracePrimitiveRetry := self objectMemoryClass basicNew integerObjectOf: 15.
  
  	TraceIsFromMachineCode := 1.
  	TraceIsFromInterpreter := 2.
  	CSCallbackEnter := 3.
  	CSCallbackLeave := 4.
  	CSEnterCriticalSection := 5.
  	CSExitCriticalSection := 6.
  	CSResume := 7.
  	CSSignal := 8.
  	CSSuspend := 9.
  	CSWait := 10.
  	CSYield := 11.
  	CSCheckEvents := 12.
  	CSThreadSchedulingLoop := 13.
  	CSOwnVM := 14.
  	CSThreadBind := 15.
  	CSSwitchIfNeccessary := 16.
  
  	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
  
  	"this is simulation only"
  	RumpCStackSize := 4096!

Item was changed:
  ----- Method: CoInterpreter 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."
  
  	^(super mustBeGlobal: var)
  	   or: [#('desiredCogCodeSize' 'heapBase'
+ 			'maxLiteralCountForCompile' 'minBackwardJumpCountForCompile') includes: var]!
- 			'maxLiteralCountForCompile' 'minBackwardJumpCountForCompile'
- 			'reenterInterpreter') includes: var]!

Item was removed:
- ----- Method: CoInterpreter class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"It is either this or scan cmacro methods for selectors."
- 	aCodeGen retainMethods: #(enterSmalltalkExecutiveImplementation)!

Item was removed:
- ----- Method: CoInterpreter>>enterSmalltalkExecutive (in category 'initialization') -----
- enterSmalltalkExecutive
- 	"Main entry-point into the interpreter at each execution level, where an
- 	 execution level is either the start of execution or reentry for a callback."
- 	<cmacro: '() enterSmalltalkExecutiveImplementation()'>
- 	"Simulation of the setjmp in enterSmalltalkExecutiveImplementation for reentry into interpreter."
- 	[([self enterSmalltalkExecutiveImplementation]
- 		on: ReenterInterpreter
- 		do: [:ex| ex return: ex returnValue]) = ReturnToInterpreter] whileTrue!

Item was removed:
- ----- Method: CoInterpreter>>enterSmalltalkExecutiveFromCallback (in category 'callback support') -----
- enterSmalltalkExecutiveFromCallback
- 	<inline: true>
- 	self enterSmalltalkExecutive!

Item was removed:
- ----- Method: CoInterpreter>>initialEnterSmalltalkExecutive (in category 'initialization') -----
- initialEnterSmalltalkExecutive
- 	"Main entry-point into the interpreter at system start-up.
- 	 In the non-threaded VM this is identical to enterSmalltalkExecutive"
- 	<cmacro: '() enterSmalltalkExecutiveImplementation()'>
- 	"Simulation of the setjmp in enterSmalltalkExecutiveImplementation for reentry into interpreter."
- 	[([self enterSmalltalkExecutiveImplementation]
- 		on: ReenterInterpreter
- 		do: [:ex| ex return: ex returnValue]) = ReturnToInterpreter] whileTrue!

Item was removed:
- ----- Method: CoInterpreter>>justActivateNewMethod (in category 'message sending') -----
- justActivateNewMethod
- 	| methodHeader activateCogMethod cogMethod numArgs numTemps rcvr initialIP |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<var: #initialIP type: #usqInt>
- 	<inline: true>
- 	methodHeader := self rawHeaderOf: newMethod.
- 	(activateCogMethod := self isCogMethodReference: methodHeader) ifTrue:
- 		[cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
- 		 methodHeader := cogMethod methodHeader].
- 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
- 	numArgs := self argumentCountOfMethodHeader: methodHeader.
- 
- 	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
- 	self assert: (objectMemory isOopForwarded: rcvr) not.
- 
- 	(activateCogMethod
- 	and: [instructionPointer asUnsignedInteger >= objectMemory startOfMemory]) ifTrue:
- 		[self iframeSavedIP: framePointer put: instructionPointer.
- 		 instructionPointer := cogit ceReturnToInterpreterPC].
- 	self push: instructionPointer.
- 	self push: framePointer.
- 	framePointer := stackPointer.
- 	initialIP := self initialIPForHeader: methodHeader method: newMethod.
- 	activateCogMethod
- 		ifTrue:
- 			[self push: cogMethod asUnsignedInteger.
- 			 self push: objectMemory nilObject. "FoxThisContext field"
- 			 instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
- 		ifFalse:
- 			[self push: newMethod.
- 			 self setMethod: newMethod methodHeader: methodHeader.
- 			 self push: objectMemory nilObject. "FoxThisContext field"
- 			 self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
- 			 self push: 0. "FoxIFSavedIP"
- 			 instructionPointer := initialIP - 1].
- 	self push: rcvr.
- 
- 	"clear remaining temps to nil"
- 	numArgs+1 to: numTemps do:
- 		[:i | self push: objectMemory nilObject].
- 
- 	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
- 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
- 		activateCogMethod ifFalse:
- 			[instructionPointer := initialIP + (self sizeOfCallPrimitiveBytecode: methodHeader)].
- 		 primFailCode ~= 0 ifTrue:
- 			[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
- 
- 	^methodHeader!

Item was added:
+ ----- Method: CoInterpreter>>justActivateNewMethod: (in category 'message sending') -----
+ justActivateNewMethod: mustBeInterpreterFrame
+ 	| methodHeader cogMethod numArgs numTemps rcvr initialIP |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #initialIP type: #usqInt>
+ 	<inline: true>
+ 	methodHeader := self rawHeaderOf: newMethod.
+ 	(mustBeInterpreterFrame not
+ 	 and: [self isCogMethodReference: methodHeader]) ifTrue:
+ 		[cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
+ 		 methodHeader := cogMethod methodHeader].
+ 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 	numArgs := self argumentCountOfMethodHeader: methodHeader.
+ 
+ 	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
+ 
+ 	(cogMethod notNil
+ 	and: [instructionPointer asUnsignedInteger >= objectMemory startOfMemory]) ifTrue:
+ 		[self iframeSavedIP: framePointer put: instructionPointer.
+ 		 instructionPointer := cogit ceReturnToInterpreterPC].
+ 	self push: instructionPointer.
+ 	self push: framePointer.
+ 	framePointer := stackPointer.
+ 	initialIP := self initialIPForHeader: methodHeader method: newMethod.
+ 	cogMethod
+ 		ifNotNil:
+ 			[self push: cogMethod asUnsignedInteger.
+ 			 self push: objectMemory nilObject. "FoxThisContext field"
+ 			 instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
+ 		ifNil:
+ 			[self push: newMethod.
+ 			 self setMethod: newMethod methodHeader: methodHeader.
+ 			 self push: objectMemory nilObject. "FoxThisContext field"
+ 			 self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
+ 			 self push: 0. "FoxIFSavedIP"
+ 			 instructionPointer := initialIP - 1].
+ 	self push: rcvr.
+ 
+ 	"clear remaining temps to nil"
+ 	numArgs+1 to: numTemps do:
+ 		[:i | self push: objectMemory nilObject].
+ 
+ 	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 cogMethod ifNil:
+ 			[instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)].
+ 		 primFailCode ~= 0 ifTrue:
+ 			[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
+ 
+ 	^methodHeader!

Item was removed:
- ----- Method: CoInterpreter>>long:jmp: (in category 'cog jit support') -----
- long: aJumpBuf jmp: returnValue
- 	"Hack simulation of setjmp/longjmp.
- 	 Signal the exception that simulates a longjmp back to the interpreter." 
- 	<doNotGenerate>
- 	aJumpBuf == reenterInterpreter ifTrue:
- 		[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: nil].
- 	aJumpBuf returnValue: returnValue; signal!

Item was changed:
  ----- Method: CoInterpreter>>saveCStackStateForCallbackContext: (in category 'callback support') -----
  saveCStackStateForCallbackContext: vmCallbackContext
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	vmCallbackContext
  		savedCStackPointer: cogit getCStackPointer;
  		savedCFramePointer: cogit getCFramePointer.
+ 	super saveCStackStateForCallbackContext: vmCallbackContext!
- 	self mem: vmCallbackContext savedReenterInterpreter asVoidPointer
- 		cp: reenterInterpreter
- 		y: (self sizeof: #'jmp_buf')!

Item was removed:
- ----- Method: CoInterpreter>>sigset:jmp: (in category 'cog jit support') -----
- sigset:aJumpBuf jmp: sigSaveMask
- 	"Hack simulation of sigsetjmp/siglongjmp.
- 	 Assign to reenterInterpreter the exception that when
- 	 raised simulates a longjmp back to the interpreter." 
- 	<doNotGenerate>
- 	reenterInterpreter := ReenterInterpreter new returnValue: 0; yourself.
- 	^0!

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."
  
  	<inline: false>
  	"If stacklimit is zero then the stack pages have not been initialized."
  	stackLimit = 0 ifTrue:
  		[^self initStackPagesAndInterpret].
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
  	self internalizeIPandSP.
- 	self fetchNextBytecode.
  	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 changed:
  ----- Method: Cogit class>>attemptToComputeTempNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeTempNamesFor: aCompiledMethod
  	(aCompiledMethod respondsTo: #tempNames) ifTrue:
  		[| schematicTemps blocks |
  		 schematicTemps := aCompiledMethod methodNode schematicTempNamesString.
  		 blocks := aCompiledMethod embeddedBlockClosures.
  		 InitializationOptions
  			at: #tempNames
+ 			put: (Dictionary newFrom: {aCompiledMethod initialPC -> (self decomposeSchematicTemps: (schematicTemps copyUpTo: $[))},
- 			put: (Dictionary withAll: {aCompiledMethod initialPC -> (self decomposeSchematicTemps: (schematicTemps copyUpTo: $[))},
  				(blocks
  					ifEmpty: [#()]
  					ifNotEmpty:
  						[aCompiledMethod embeddedBlockClosures
  							with: (schematicTemps piecesCutWhere: [:a :b| b = $[]) allButFirst
  							collect: [:c :s| c startpc -> (self decomposeSchematicTemps: (s copyWithoutAll: '[]'))]]))]!

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn'
- 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn'
  	classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterPrimitives commentStamp: 'eem 12/7/2017 18:44' prior: 0!
  InterpreterPrimitives implements most of the VM's core primitives.  It is the root of the interpreter hierarchy so as to share the core primitives amongst the varioius interpreters.
  
  Instance Variables
  	argumentCount:			<Integer>
  	messageSelector:			<Integer>
  	newMethod:				<Integer>
  	nextProfileTick:				<Integer>
  	objectMemory:				<ObjectMemory> (simulation only)
  	preemptionYields:			<Boolean>
  	primFailCode:				<Integer>
  	osErrorCode:				<Integer>
  	profileMethod:				<Integer>
  	profileProcess:				<Integer>
  	profileSemaphore:			<Integer>
  	secHasEnvironmentAccess <Integer>
  
  argumentCount
  	- the number of arguments of the current message
  
  messageSelector
  	- the oop of the selector of the current message
  
  newMethod
  	- the oop of the result of looking up the current message
  
  nextProfileTick
  	- the millisecond clock value of the next profile tick (if profiling is in effect)
  
  objectMemory
  	- the memory manager and garbage collector that manages the heap
  
  preemptionYields
  	- a boolean controlling the process primitives.  If true (old, incorrect, blue-book semantics) a preempted process is sent to the back of its run-queue.  If false, a process preempted by a higher-priority process is put back at the head of its run queue, hence preserving cooperative scheduling within priorities.
  
  primFailCode
  	- primitive success/failure flag, 0 for success, otherwise the reason code for failure
  
  osErrorCode
  	- a 64-bit value settable by external primitives conveying arbitrary error codes from the operating system and/or system libraries
  
  profileMethod
  	- the oop of the method at the time nextProfileTick was reached
  
  profileProcess
  	- the oop of the activeProcess at the time nextProfileTick was reached
  
  profileSemaphore
  	- the oop of the semaphore to signal when nextProfileTick is reached
  
  secHasEnvironmentAccess
  	- the function to call to check if access to the envronment should be granted to primitiveGetenv
  !

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveFailForFFIException:at: (in category 'primitive support') -----
+ primitiveFailForFFIException: exceptionCode at: pc
+ 	<var: 'exceptionCode' type: #sqLong>
+ 	"Set PrimErrOSError primitive failure and associated osErrorCode."
+ 	<api>
+ 	osErrorCode := exceptionCode.
+ 	exceptionPC := pc.
+ 	^primFailCode := PrimErrFFIException!

Item was added:
+ ----- Method: Object>>perform:with:with:with:with:with: (in category '*VMMaker-message handling') -----
+ perform: aSymbol with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject
+ 	"Send the selector, aSymbol, to the receiver with the given arguments.
+ 	Fail if the number of arguments expected by the selector is not five.
+ 	Primitive. Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject. secondObject. thirdObject. fourthObject. fifthObject }!

Item was added:
+ ----- Method: Object>>perform:with:with:with:with:with:with: (in category '*VMMaker-message handling') -----
+ perform: aSymbol with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject
+ 	"Send the selector, aSymbol, to the receiver with the given arguments.
+ 	Fail if the number of arguments expected by the selector is not six.
+ 	Primitive. Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject. secondObject. thirdObject. fourthObject. fifthObject. sixthObject }!

Item was added:
+ ----- Method: SpurMemoryManager>>activateFailingPrimitiveMethod (in category 'simulation only') -----
+ activateFailingPrimitiveMethod
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter activateFailingPrimitiveMethod!

Item was added:
+ ----- Method: SpurMemoryManager>>is:KindOfClass: (in category 'simulation only') -----
+ is: oop KindOfClass: aClass
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter is: oop KindOfClass: aClass!

Item was added:
+ ----- Method: SpurMemoryManager>>primitiveFailForFFIException:at: (in category 'simulation only') -----
+ primitiveFailForFFIException: errorCode at: pc
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter primitiveFailForFFIException: errorCode at: pc!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	LowcodeVM ifTrue: [ aCCodeGenerator addHeaderFile:'"sqLowcodeFFI.h"'].
  
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: #usqInt.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
  	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'bytecodeSetSelector'].
  	BytecodeSetHasExtensions == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'sqIntptr_t methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	NewspeakVM
  		ifTrue:
  			[aCCodeGenerator
  				var: #nsMethodCache
  				declareC: 'sqIntptr_t nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]']
  		ifFalse:
  			[aCCodeGenerator
  				removeVariable: #nsMethodCache;
  				removeVariable: 'localAbsentReceiver';
  				removeVariable: 'localAbsentReceiverOrZero'].
  	AtCacheTotalSize isInteger ifTrue:
  		[aCCodeGenerator
  			var: #atCache
  			declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'].
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #displayBits type: #'void *'.
  	self declareC: #(displayWidth displayHeight displayDepth) as: #int in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  			declareC: 'void (*primitiveFunctionPointer)()';
  		var: #externalPrimitiveTable
  			declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)';
  		var: #interruptCheckChain
  			declareC: 'void (*interruptCheckChain)(void) = 0';
  		var: #showSurfaceFn
  			declareC: 'int (*showSurfaceFn)(sqIntptr_t, int, int, int, int)';
  		var: #jmpBuf
  			declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]';
  		var: #suspendedCallbacks
  			declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]';
  		var: #suspendedMethods
  			declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce
  								statIdleUsecs)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong.
+ 	aCCodeGenerator
+ 		var: #reenterInterpreter
+ 		declareC: 'jmp_buf reenterInterpreter; /* private export */'.
- 	
  	LowcodeVM
  		ifTrue:
  			[aCCodeGenerator
  				var: #lowcodeCalloutState type: #'sqLowcodeCalloutState*'.
  			 self declareC: #(nativeSP nativeStackPointer shadowCallStackPointer)
  				as: #'char *'
  				in: aCCodeGenerator]
  		ifFalse:
  			[#(lowcodeCalloutState nativeSP nativeStackPointer shadowCallStackPointer) do:
  				[:var| aCCodeGenerator removeVariable: var]]!

Item was changed:
  ----- Method: StackInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	STACKVM := true.
  
  	"These flags function to identify a GC operation, or
  	 to specify what operations the leak checker should be run for."
  	GCModeFull := 1.				"stop-the-world global GC"
  	GCModeNewSpace := 2.		"Spur's scavenge, or V3's incremental"
  	GCModeIncremental := 4.		"incremental global gc (Dijkstra tri-colour marking); as yet unimplemented"
  	GCModeBecome := 8.			"v3 post-become sweeping/Spur forwarding"
  	GCModeImageSegment := 16.	"just a flag for leak checking image segments"
  	GCModeFreeSpace := 32.		"just a flag for leak checking free space; Spur only"
  	GCCheckPrimCall := 64.		"just a flag for leak checking external primitive calls"
  
  	StackPageTraceInvalid := -1.
  	StackPageUnreached := 0.
  	StackPageReachedButUntraced := 1.
  	StackPageTraced := 2.
  
  	DumpStackOnLowSpace := 0.
  	MillisecondClockMask := 16r1FFFFFFF.
  	"Note: The external primitive table should actually be dynamically sized but for the sake of inferior platforms (e.g., Mac :-) who cannot allocate memory in any reasonable way, we keep it static (and cross our fingers...)"
  	MaxExternalPrimitiveTableSize := 4096. "entries"
  
  	MaxJumpBuf := 32. "max. callback depth"
  	FailImbalancedPrimitives := InitializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].
+ 	EnforceAccessControl := InitializationOptions at: #EnforceAccessControl ifAbsent: [true].
+ 
+ 	ReturnToInterpreter := 1 "setjmp/longjmp code."!
- 	EnforceAccessControl := InitializationOptions at: #EnforceAccessControl ifAbsent: [true]!

Item was changed:
  ----- Method: StackInterpreter 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."
  
  	^(super mustBeGlobal: var)
  	   or: [(self objectMemoryClass mustBeGlobal: var)
  	   or: [(#('interpreterProxy' 'interpreterVersion' 'inIOProcessEvents'
  			'deferDisplayUpdates' 'extraVMMemory'
  			'showSurfaceFn' 'displayBits' 'displayWidth' 'displayHeight' 'displayDepth'
  			'desiredNumStackPages' 'desiredEdenBytes'
  			'breakLookupClassTag' 'breakSelector' 'breakSelectorLength' 'sendTrace' 'checkAllocFiller' 'checkedPluginName'
+ 			'reenterInterpreter' 'suppressHeartbeatFlag'
+ 			'debugCallbackInvokes' 'debugCallbackPath' 'debugCallbackReturns') includes: var)
- 			'suppressHeartbeatFlag' 'debugCallbackInvokes' 'debugCallbackPath' 'debugCallbackReturns') includes: var)
  	   or: [ "This allows slow machines to define bytecodeSetSelector as 0
  			to avoid the interpretation overhead."
  			MULTIPLEBYTECODESETS not and: [var = 'bytecodeSetSelector']]]]!

Item was added:
+ ----- Method: StackInterpreter class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
+ prepareToBeAddedToCodeGenerator: aCodeGen
+ 	"It is either this or scan cmacro methods for selectors."
+ 	aCodeGen retainMethods: #(enterSmalltalkExecutiveImplementation)!

Item was added:
+ ----- Method: StackInterpreter>>activateFailingPrimitiveMethod (in category 'primitive support') -----
+ activateFailingPrimitiveMethod
+ 	"Assuming the primFailCode (and any other relevant failure state) has been set,
+ 	 switch the VM to the interpreter if necessary (if in the CoInterpreter executing machine code),
+ 	 and activate the newMethod (which is expected to have a primitive)."
+ 	<api>
+ 	self assert: primFailCode ~= 0.
+ 	self assert: (objectMemory addressCouldBeObj: newMethod).
+ 	self assert: (objectMemory isCompiledMethod: newMethod).
+ 	self assert: (self primitiveIndexOf: newMethod) ~= 0.
+ 	self justActivateNewMethod: true. "Frame must be interpreted"
+ 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
+ 	"NOTREACHED"
+ 	^nil!

Item was changed:
  ----- Method: StackInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| methodHeader |
+ 	methodHeader := self justActivateNewMethod: false. "either interpreted or machine code"
- 	methodHeader := self justActivateNewMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	stackPointer < stackLimit ifTrue:
  		[self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader)]!

Item was changed:
  ----- Method: StackInterpreter>>callbackEnter: (in category 'callback support') -----
  callbackEnter: callbackID
+ 	"Re-enter the interpreter to execute a (non-ALien,non-FFI) callback (as used by the Python bridge)."
+ 	<volatile>
- 	"Re-enter the interpreter for executing a callback"
  	<export: true>
  	<var: #callbackID type: #'sqInt *'>
+ 	| savedReenterInterpreter |
+ 	<var: #savedReenterInterpreter type: #'jmp_buf'>
  
  	"For now, do not allow a callback unless we're in a primitiveResponse"
  	(self asserta: primitiveFunctionPointer ~= 0) ifFalse:
  		[^false].
  
+ 	self assert: primFailCode = 0.
+ 
  	"Check if we've exceeded the callback depth"
  	(self asserta: jmpDepth < MaxJumpBuf) ifFalse:
  		[^false].
  	jmpDepth := jmpDepth + 1.
  
  	"Suspend the currently active process"
  	suspendedCallbacks at: jmpDepth put: self activeProcess.
  	"We need to preserve newMethod explicitly since it is not activated yet
  	and therefore no context has been created for it. If the caller primitive
  	for any reason decides to fail we need to make sure we execute the correct
  	method and not the one 'last used' in the call back"
  	suspendedMethods at: jmpDepth put: newMethod.
  	"Signal external semaphores since a signalSemaphoreWithIndex: request may
  	 have been issued immediately prior to this callback before the VM has any
  	 chance to do a signalExternalSemaphores in checkForEventsMayContextSwitch:"
  	self signalExternalSemaphores.
  	"If no process is awakened by signalExternalSemaphores then transfer
  	 to the highest priority runnable one."
  	(suspendedCallbacks at: jmpDepth) = self activeProcess ifTrue:
  		[self transferTo: self wakeHighestPriority].
  
  	"Typically, invoking the callback means that some semaphore has been 
  	signaled to indicate the callback. Force an interrupt check as soon as possible."
  	self forceInterruptCheck.
  
+ 	"Save the previous interpreter entry jmp_buf."
+ 	self mem: savedReenterInterpreter asVoidPointer
+ 		cp: reenterInterpreter
+ 		y: (self sizeof: #'jmp_buf').
  	(self setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
  		[callbackID at: 0 put: jmpDepth.
+ 		 self enterSmalltalkExecutive.
+ 		 self assert: false "NOTREACHED"].
- 		self interpret].
  
+ 	"Restore the previous interpreter entry jmp_buf."
+ 	self mem: reenterInterpreter
+ 		cp: (self cCoerceSimple: savedReenterInterpreter to: #'void *')
+ 		y: (self sizeof: #'jmp_buf').
+ 
  	"Transfer back to the previous process so that caller can push result"
  	self putToSleep: self activeProcess yieldingIf: preemptionYields.
  	self transferTo: (suspendedCallbacks at: jmpDepth).
  	newMethod := suspendedMethods at: jmpDepth.	"see comment above"
  	argumentCount := self argumentCountOf: newMethod.
+ 	self assert: primFailCode = 0.
+ 	jmpDepth := jmpDepth - 1.
- 	jmpDepth := jmpDepth-1.
- 	"clean out the primPops etc since we'll be returning via primitive"
- 	self initPrimCall.
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>cloneOSErrorObj:numSlots: (in category 'message sending') -----
  cloneOSErrorObj: errObj numSlots: numSlots
  	"If errObj is a pointer object with at least two slots, then answer a clone
+ 	  of the error object with the second slot set to the value of osErrorCode,
+ 	  and if an PrimErrFFIException, then the third slow with the exceptionPC."
- 	  of the error object with the second slot set to the value of osErrorCode."
  	| clone |
  	<inline: true>
  	clone := objectMemory hasSpurMemoryManagerAPI
  				ifTrue: [objectMemory
  							eeInstantiateSmallClassIndex: (objectMemory classIndexOf: errObj)
  							format: objectMemory nonIndexablePointerFormat
  							numSlots: numSlots]
  				ifFalse: [objectMemory
  							eeInstantiateSmallClass: (objectMemory fetchClassOfNonImm: errObj)
  							numSlots: numSlots].
  	0 to: numSlots - 1 do:
  		[:i| objectMemory
  				storePointerUnchecked: i
  				ofObject: clone
  				withValue: (objectMemory fetchPointer: i ofObject: errObj)].
+ 	(numSlots > 2
+ 	 and: [primFailCode = PrimErrFFIException])
+ 		ifTrue:
+ 			[objectMemory
+ 				storePointerUnchecked: 1
+ 					ofObject: clone
+ 						withValue: (self positive64BitIntegerFor: osErrorCode);
+ 				storePointerUnchecked: 2
+ 					ofObject: clone
+ 						withValue: (self positive64BitIntegerFor: exceptionPC)]
+ 		ifFalse:
+ 			[objectMemory
+ 				storePointerUnchecked: 1
+ 				ofObject: clone
+ 				withValue: (self signed64BitIntegerFor: osErrorCode)].
- 	objectMemory
- 		storePointerUnchecked: 1
- 		ofObject: clone
- 		withValue: (self signed64BitIntegerFor: osErrorCode).
  	^clone!

Item was added:
+ ----- Method: StackInterpreter>>enterSmalltalkExecutive (in category 'initialization') -----
+ enterSmalltalkExecutive
+ 	"Main entry-point into the interpreter at each execution level, where an
+ 	 execution level is either the start of execution or reentry for a callback."
+ 	<cmacro: '() enterSmalltalkExecutiveImplementation()'>
+ 	"Simulation of the setjmp in enterSmalltalkExecutiveImplementation for reentry into interpreter."
+ 	[([self enterSmalltalkExecutiveImplementation]
+ 		on: ReenterInterpreter
+ 		do: [:ex| ex return: ex returnValue]) = ReturnToInterpreter] whileTrue!

Item was changed:
  ----- Method: StackInterpreter>>enterSmalltalkExecutiveFromCallback (in category 'callback support') -----
  enterSmalltalkExecutiveFromCallback
  	<inline: true>
+ 	self enterSmalltalkExecutive!
- 	self interpret!

Item was added:
+ ----- Method: StackInterpreter>>enterSmalltalkExecutiveImplementation (in category 'initialization') -----
+ enterSmalltalkExecutiveImplementation
+ 	"Main entry-point into the interpreter at each execution level, where an execution
+ 	 level is either the start of execution or reentry for a callback.
+ 	 This is the actual implementation, separated from enterSmalltalkExecutive so the
+ 	 simulator can wrap it in an exception handler and hence simulate the setjmp/longjmp."
+ 	<inline: false>
+ 	"Setjmp for reentry into interpreter from elsewhere, e.g. FFI exception primitive failure."
+ 	self sigset: reenterInterpreter jmp: 0.
+ 	self setMethod: (self frameMethod: framePointer).
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
+ 	self interpret.
+ 	^0!

Item was changed:
  ----- Method: StackInterpreter>>getErrorObjectFromPrimFailCode (in category 'message sending') -----
  getErrorObjectFromPrimFailCode
  	"Answer the errorCode object to supply to a failing primitive method that accepts one.
  	 If there is a primitive error table and the primFailCode is a valid index there-in answer
  	 the corresponding entry in the table, otherwise simply answer the code as an integer."
  	| table errObj numSlots |
  	primFailCode > 0 ifTrue:
  		[table := objectMemory splObj: PrimErrTableIndex.
  		 primFailCode <= (objectMemory numSlotsOf: table) ifTrue:
  			[errObj := objectMemory followField: primFailCode - 1 ofObject: table.
+ 			 "If this is a PrimErrOSError/PrimErrFFIException and there's a clonable object in the table at that index,
- 			 "If this is a PrimErrOSError and there's a clonable object in the table at that index,
  			 answer a clone of the error object with the second slot set to the value of osErrorCode."
+ 			 ((primFailCode = PrimErrOSError or: [primFailCode = PrimErrFFIException])
- 			 (primFailCode = PrimErrOSError
  			  and: [(objectMemory formatOf: errObj) = objectMemory nonIndexablePointerFormat
  			  and: [(numSlots := objectMemory numSlotsOf: errObj) >= 2]]) ifTrue:
  				[errObj := self cloneOSErrorObj: errObj numSlots: numSlots].
  			 ^errObj]].
  	^objectMemory integerObjectOf: primFailCode!

Item was changed:
  ----- Method: StackInterpreter>>initStackPagesAndInterpret (in category 'initialization') -----
  initStackPagesAndInterpret
  	"Initialize the stack pages and enter interpret. Use alloca'ed memory so that when
  	 we have a JIT its stack pointer will be on the native stack since alloca allocates
  	 memory on the stack. Certain thread systems use the native stack pointer as the
  	 frame ID so putting the stack anywhere else can confuse the thread system."
  
  	"This should be in its own initStackPages method but Slang can't inline
  	 C code strings."
  	| stackPageBytes stackPagesBytes theStackMemory |
  	<var: #theStackMemory type: #'void *'>
  	stackPageBytes := self stackPageByteSize.
  	stackPagesBytes := self computeStackZoneSize.
  	theStackMemory := self
  							cCode: [self alloca: stackPagesBytes]
  							inSmalltalk: [stackPages initializeWithByteSize: stackPagesBytes for: self].
  	self cCode: [self me: theStackMemory ms: 0 et: stackPagesBytes].
  	stackPages
  		initializeStack: theStackMemory
  		numSlots: stackPagesBytes / objectMemory wordSize
  		pageSize: stackPageBytes / objectMemory wordSize.
  
  	"Once the stack pages are initialized we can continue to bootstrap the system."
  	self loadInitialContext.
  	"We're ready for the heartbeat (poll interrupt)"
  	self ioInitHeartbeat.
+ 	self initialEnterSmalltalkExecutive.
- 	self interpret.
  	^nil!

Item was added:
+ ----- Method: StackInterpreter>>initialEnterSmalltalkExecutive (in category 'initialization') -----
+ initialEnterSmalltalkExecutive
+ 	"Main entry-point into the interpreter at system start-up.
+ 	 In the non-threaded VM this is identical to enterSmalltalkExecutive"
+ 	<cmacro: '() enterSmalltalkExecutiveImplementation()'>
+ 	"Simulation of the setjmp in enterSmalltalkExecutiveImplementation for reentry into interpreter."
+ 	[([self enterSmalltalkExecutiveImplementation]
+ 		on: ReenterInterpreter
+ 		do: [:ex| ex return: ex returnValue]) = ReturnToInterpreter] whileTrue!

Item was changed:
  ----- Method: StackInterpreter>>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 browser plugin VM, however, it 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].
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
  	self internalizeIPandSP.
- 	self fetchNextBytecode.
  	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: StackInterpreter>>justActivateNewMethod (in category 'message sending') -----
- justActivateNewMethod
- 	| methodHeader numArgs numTemps rcvr |
- 	<inline: true>
- 	methodHeader := objectMemory methodHeaderOf: newMethod.
- 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
- 	numArgs := self argumentCountOfMethodHeader: methodHeader.
- 
- 	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
- 	self assert: (objectMemory isOopForwarded: rcvr) not.
- 
- 	self push: instructionPointer.
- 	self push: framePointer.
- 	framePointer := stackPointer.
- 	self push: newMethod.
- 	self setMethod: newMethod methodHeader: methodHeader.
- 	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
- 	self push: objectMemory nilObject. "FxThisContext field"
- 	self push: rcvr.
- 
- 	"clear remaining temps to nil"
- 	numArgs+1 to: numTemps do:
- 		[:i | self push: objectMemory nilObject].
- 
- 	instructionPointer := (self initialIPForHeader: methodHeader method: newMethod) - 1.
- 
- 	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
- 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
- 		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
- 		 primFailCode ~= 0 ifTrue:
- 			[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
- 
- 	^methodHeader!

Item was added:
+ ----- Method: StackInterpreter>>justActivateNewMethod: (in category 'message sending') -----
+ justActivateNewMethod: mustBeInterpreterFrame
+ 	| methodHeader numArgs numTemps rcvr |
+ 	<inline: true>
+ 	methodHeader := objectMemory methodHeaderOf: newMethod.
+ 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 	numArgs := self argumentCountOfMethodHeader: methodHeader.
+ 
+ 	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
+ 
+ 	self push: instructionPointer.
+ 	self push: framePointer.
+ 	framePointer := stackPointer.
+ 	self push: newMethod.
+ 	self setMethod: newMethod methodHeader: methodHeader.
+ 	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
+ 	self push: objectMemory nilObject. "FxThisContext field"
+ 	self push: rcvr.
+ 
+ 	"clear remaining temps to nil"
+ 	numArgs+1 to: numTemps do:
+ 		[:i | self push: objectMemory nilObject].
+ 
+ 	instructionPointer := (self initialIPForHeader: methodHeader method: newMethod) - 1.
+ 
+ 	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
+ 
+ 	^methodHeader!

Item was added:
+ ----- Method: StackInterpreter>>long:jmp: (in category 'simulation') -----
+ long: aJumpBuf jmp: returnValue
+ 	"Hack simulation of setjmp/longjmp.
+ 	 Signal the exception that simulates a longjmp back to the interpreter." 
+ 	<doNotGenerate>
+ 	aJumpBuf == reenterInterpreter ifTrue:
+ 		[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: nil].
+ 	aJumpBuf returnValue: returnValue; signal!

Item was changed:
+ ----- Method: StackInterpreter>>objectMemory (in category 'simulation support') -----
- ----- Method: StackInterpreter>>objectMemory (in category 'cog jit support') -----
  objectMemory
  	<doNotGenerate>
  	^objectMemory!

Item was changed:
  ----- Method: StackInterpreter>>restoreCStackStateForCallbackContext: (in category 'callback support') -----
  restoreCStackStateForCallbackContext: vmCallbackContext
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
+ 	self mem: reenterInterpreter
+ 		cp: vmCallbackContext savedReenterInterpreter asVoidPointer
+ 		y: (self sizeof: #'jmp_buf')!
- 	"this is a no-op for the Stack VM"!

Item was changed:
  ----- Method: StackInterpreter>>saveCStackStateForCallbackContext: (in category 'callback support') -----
  saveCStackStateForCallbackContext: vmCallbackContext
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
+ 	self mem: vmCallbackContext savedReenterInterpreter asVoidPointer
+ 		cp: reenterInterpreter
+ 		y: (self sizeof: #'jmp_buf')!
- 	"this is a no-op for the Stack VM"!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallback:Stack:Registers:Jmpbuf: (in category 'callback support') -----
  sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr
  	"Send the 4 argument callback message invokeCallback:stack:registers:jmpbuf:
  	 to Alien class with the supplied args.  The arguments are raw C addresses
  	 and are converted to integer objects on the way."
  	<export: true>
  	| classTag |
  	classTag := self fetchClassTagOfNonImm: (self splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	argumentCount := 4.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
  	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
  	((self argumentCountOf: newMethod) = 4
  	and: [primitiveFunctionPointer = 0]) ifFalse:
  		[^false].
  	self push: (self splObj: ClassAlien). "receiver"
  	self push: (self positiveMachineIntegerFor: thunkPtr).
  	self push: (self positiveMachineIntegerFor: stackPtr).
  	self push: (self positiveMachineIntegerFor: regsPtr).
  	self push: (self positiveMachineIntegerFor: jmpBufPtr).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
+ 	self justActivateNewMethod: false. "either interpreted or machine code"
- 	self justActivateNewMethod.
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self checkForStackOverflow.
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallbackContext: (in category 'callback support') -----
  sendInvokeCallbackContext: vmCallbackContext
  	"Send the calllback message to Alien class with the supplied arg(s).  Use either the 1 arg
  	 invokeCallbackContext: or the 4 arg invokeCallback:stack:registers:jmpbuf: message,
  	 depending on what selector is installed in the specialObjectsArray. Note that if invoking the
  	 legacy invokeCallback:stack:registers:jmpbuf: we pass the vmCallbackContext as the jmpbuf
  	 argument (see reestablishContextPriorToCallback:). The arguments are raw C addresses and
  	 are converted to integer objects on the way. sendInvokeCallbackContext: &
  	 returnAs:ThroughCallback:Context: along with ownVM: and disownVM: conspire to save and
  	 restore newMethod, argumentCount and primitiveFunctionPointer around a callback.
  	 The VM depends on argumentCount being correct to cut-back the correct number of
  	 arguments on primitive return.  If a primitive that invokes a callback fails after invoking a
  	 callback (a bad idea, but s**t happens during development) then newMethod is required to
  	 activate the right faling method, and Spur expects primitiveFunctionPointer to be valid, so
  	 asserts will fail misleadingly if not."
  	<export: true>
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	| classTag |
  	vmCallbackContext savedPrimFunctionPointer: primitiveFunctionPointer.
  	classTag := self fetchClassTagOfNonImm: (objectMemory splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
  	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
  	primitiveFunctionPointer ~= 0 ifTrue:
  		[primitiveFunctionPointer := vmCallbackContext savedPrimFunctionPointer.
  		 ^false].
  	self assert: (debugCallbackInvokes := debugCallbackInvokes + 1) > 0.
  	"self assert: debugCallbackInvokes < 3802."
  	self saveCStackStateForCallbackContext: vmCallbackContext.
  	self push: (objectMemory splObj: ClassAlien). "receiver"
  	(self argumentCountOf: newMethod) = 4 ifTrue:
  		[self push: (self positiveMachineIntegerFor: vmCallbackContext thunkp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext stackp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext intregargsp asUnsignedInteger)].
  	self push: (self positiveMachineIntegerFor: vmCallbackContext asUnsignedInteger).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
+ 	self justActivateNewMethod: false. "either interpreted or machine code"
- 	self justActivateNewMethod.
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self checkForStackOverflow.
  	self assert: (self frameReceiver: framePointer) = (objectMemory splObj: ClassAlien).
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!

Item was added:
+ ----- Method: StackInterpreter>>siglong:jmp: (in category 'primitive support') -----
+ siglong: aJumpBuf jmp: returnValue
+ 	^self long: aJumpBuf jmp: returnValue!

Item was added:
+ ----- Method: StackInterpreter>>sigset:jmp: (in category 'primitive support') -----
+ sigset: aJumpBuf jmp: sigSaveMask
+ 	"Hack simulation of sigsetjmp/siglongjmp.
+ 	 Assign to reenterInterpreter the exception that when
+ 	 raised simulates a longjmp back to the interpreter." 
+ 	<doNotGenerate>
+ 	reenterInterpreter := ReenterInterpreter new returnValue: 0; yourself.
+ 	^0!

Item was changed:
  ----- Method: StackInterpreter>>snapshot: (in category 'image save/restore') -----
  snapshot: embedded 
  	"update state of active context"
  	| activeContext activeProc rcvr setMacType stackIndex |
  	<var: #setMacType type: #'void *'>
  
  	"For now the stack munging below doesn't deal with more than one argument.
  	 It can, and should."
  	argumentCount ~= 0 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  
  	"Need to convert all frames into contexts since the snapshot file only holds objects."
  	self push: instructionPointer.
  	activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: true.
  
  	"update state of active process"
  	activeProc := self activeProcess.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  
  	tempOop := activeContext.
  	objectMemory garbageCollectForSnapshot.
  	"Nothing moves from here on so it is safe to grab the activeContext again."
  	activeContext := tempOop.
  	tempOop := 0.
  
  	self successful ifTrue:
  		["Without contexts or stacks simulate
  			rcvr := self popStack. ''pop rcvr''
  			self push: trueObj.
  		  to arrange that the snapshot resumes with true.  N.B. stackIndex is one-relative."
  		stackIndex := self quickFetchInteger: StackPointerIndex ofObject: activeContext.
  		rcvr := objectMemory fetchPointer: stackIndex + CtxtTempFrameStart - 1 ofObject: activeContext.
  		objectMemory
  			storePointerUnchecked: stackIndex + CtxtTempFrameStart - 1
  			ofObject: activeContext
  			withValue: objectMemory trueObject.
  		"now attempt to write the snapshot file"
  		self writeImageFileIO.
  		(self successful and: [embedded not]) ifTrue:
  			["set Mac file type and creator; this is a noop on other platforms"
  			setMacType := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
  			setMacType = 0 ifFalse:
  				[self cCode: '((sqInt (*)(char *, char *, char *))setMacType)(imageName, "STim", "FAST")']].
  		"Without contexts or stacks simulate
  			self pop: 1"
  		objectMemory
  			storePointerUnchecked: StackPointerIndex
  			ofObject: activeContext
  			withValue: (objectMemory integerObjectOf: stackIndex - 1)].
  
  	objectMemory postSnapshot.
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  	self successful
  		ifTrue: [self push: objectMemory falseObject]
  		ifFalse:
  			[self push: rcvr.
+ 			 self justActivateNewMethod: true] "no point checking for machine code; there isn't any at this point"!
- 			 self justActivateNewMethod]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>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."
+ 
+ 	<inline: false>
+ 	"If stacklimit is zero then the stack pages have not been initialized."
+ 	stackLimit = 0 ifTrue:
+ 		[^self initStackPagesAndInterpret].
+ 	"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 changed:
  ----- Method: StackInterpreterSimulator>>run (in category 'testing') -----
  run
  	"Just run"
  	quitBlock := [displayView ifNotNil:
  				   [displayView containingWindow ifNotNil:
  					[:topWindow|
  					((World submorphs includes: topWindow)
  					 and: [UIManager default confirm: 'close?']) ifTrue:
  						[topWindow delete]]].
  				  ^self close].
  	self initStackPages.
  	self loadInitialContext.
+ 	self initialEnterSmalltalkExecutive.
- 	self internalizeIPandSP.
- 	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!

Item was changed:
  ----- Method: TMethod>>removeUnusedTempsAndNilIfRequiredIn: (in category 'utilities') -----
  removeUnusedTempsAndNilIfRequiredIn: aCodeGen
  	"Remove all of the unused temps in this method. Answer a set of the references.
  	 As a side-effect introduce explicit temp := nil statements for temps that are
  	 tested for nil before necessarily being assigned."
  	| refs readBeforeAssigned simplyTypedLocals |
  	refs := self removeUnusedTempsIn: aCodeGen.
  	"reset the locals to be only those still referred to"
  	locals := locals select: [:e| refs includes: e].
  	(locals notEmpty
  	 and: [aCodeGen
  			pushScope: declarations
  			while: [simplyTypedLocals := locals select:
  											[:var|
  											 declarations
  												at: var
  												ifPresent: [:decl| aCodeGen isSimpleType: (aCodeGen extractTypeFor: var fromDeclaration: decl)]
  												ifAbsent: [true]].
  				(readBeforeAssigned := (self findReadBeforeAssignedIn: simplyTypedLocals in: aCodeGen)) notEmpty]]) ifTrue:
  		[readBeforeAssigned := readBeforeAssigned reject:
+ 			[:v| | d | "don't initialize externs, statics, arrays or the explicitly initialized."
- 			[:v| | d | "don't initialize externs, arrays or the explicitly initialized."
  			 d := self declarationAt: v.
+ 			 (d beginsWith: 'extern') or: [(d beginsWith: 'static') or: [(d includes: $[) or: [d includes: $=]]]].
- 			 (d beginsWith: 'extern') or: [(d includes: $[) or: [d includes: $=]]].
  		 parseTree statements addAllFirst:
  			(readBeforeAssigned asSortedCollection collect:
+ 				[:var| | varNode varType zeroNode |
+ 				 varNode := TVariableNode new setName: var; yourself.
+ 				 varType := aCodeGen typeFor: varNode in: self.
+ 				 zeroNode := TConstantNode new setValue: 0; yourself.
+ 				 TAssignmentNode new
+ 					setVariable: varNode
+ 					expression: (((aCodeGen isIntegralCType: varType)
+ 								    or: [aCodeGen isFloatingPointCType: varType])
+ 									ifTrue: [zeroNode]
+ 									ifFalse: [aCodeGen nodeToCast: zeroNode to: varType])])].
- 				[:var|
- 				TAssignmentNode new
- 					setVariable: (TVariableNode new setName: var; yourself)
- 					expression: (TConstantNode new setValue: 0; yourself)])].
  	^refs!

Item was changed:
  ----- Method: TStmtListNode>>addReadBeforeAssignedIn:to:assignments:in: (in category 'utilities') -----
  addReadBeforeAssignedIn: variables to: readBeforeAssigned assignments: assigned in: aCodeGen
  	"Add any variables in variables that are read before written to readBeforeAssigned.
  	 Add unconditional assignments to assigned.  For convenience answer assigned."
  	self
  		nodesWithParentsDo:
  			[:node :parent|
  			(node isAssignment
  			 and: [variables includes: node variable name]) ifTrue:
  				[assigned add: node variable name].
  			(node isVariable
  			 and: [(variables includes: node name)
  			 and: [(assigned includes: node name) not
+ 			 and: [(#(nil pointer) includes: (node structTargetKindIn: aCodeGen))
- 			 and: [(node structTargetKindIn: aCodeGen) isNil
  			 and: [(parent notNil and: [parent isAssignment and: [parent variable == node]]) not]]]]) ifTrue:
  				[node name = 'theCalloutState' ifTrue:
  					[self halt].
  				 readBeforeAssigned add: node name]]
  		unless:
  			[:node :parent| | conditionalAssignments mayHaveSideEffects |
  			node isSend
  				ifTrue:
  					["First deal with implicit assignments..."
  					node isValueExpansion ifTrue:
  						[assigned addAll: node receiver args].
  					(#(mem:cp:y: mem:mo:ve:) includes: node selector) ifTrue:
  						[assigned add: (node args first detect: [:subnode| subnode isVariable]) name].
  					(#(to:do: to:by:do:) includes: node selector) ifTrue:
  						[assigned addAll: (node args at: node selector numArgs) args.
  						 mayHaveSideEffects := node args size = 4. "See TMethod>>prepareMethodIn:"
  						 mayHaveSideEffects ifTrue:
  							[assigned add: node args last name]].
  					"Then deal with read-before-written in the arms of conditionals..."
  					(#(ifTrue: ifFalse: ifNil: ifNotNil:) intersection: node selector keywords) notEmpty
  						ifTrue:
  							["First find assignments in the expression..."
  							 (TStmtListNode new setStatements: {node receiver}; yourself)
  								addReadBeforeAssignedIn: variables
  								to: readBeforeAssigned
  								assignments: assigned
  								in: aCodeGen.
  							 "Now find read-before-written in each arm, and collect the assignments to spot those assigned in both arms"
  							 conditionalAssignments :=
  								node args
  									collect:
  										[:block|
  										block isStmtList ifTrue:
  											[block
  												addReadBeforeAssignedIn: variables
  												to: readBeforeAssigned
  												assignments: assigned copy
  												in: aCodeGen]]
  									thenSelect: [:each| each notNil].
  							 "add to assigned those variables written to in both arms"
  							 conditionalAssignments size = 2 ifTrue:
  								[conditionalAssignments := conditionalAssignments collect: [:set| set difference: assigned].
  								 assigned addAll: (conditionalAssignments first intersection: conditionalAssignments last)].
  							 true]
  						ifFalse:
  							[false]]
  				ifFalse:
  					[false]].
  	^assigned!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>dispatchFunctionPointer: (in category 'callout support') -----
  dispatchFunctionPointer: aFunctionPointer
  	"In C aFunctionPointer is void (*aFunctionPointer)()"
  	<cmacro: '(aFunctionPointer) (aFunctionPointer)()'>
+ 	"To write the FFI call failure code we simulate invoking the production VM's
+ 	 fatal exception handlers (sigsegv on Unix, squeakExceptionHandler on WIN32, et al)."
+ 	^[self perform: aFunctionPointer]
+ 		on: Error
+ 		do: [:ex|
+ 			interpreterProxy
+ 				primitiveFailForFFIException: PrimErrFFIException at: aFunctionPointer asInteger;
+ 				activateFailingPrimitiveMethod]!
- 	^self perform: aFunctionPointer!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>dispatchFunctionPointer:with:with:with:with: (in category 'callout support') -----
  dispatchFunctionPointer: aFunctionPointer with: int1 with: int2 with: int3 with: int4
  	"In C aFunctionPointer is void (*aFunctionPointer)(int, int, int, int)"
  	<cmacro: '(aFunctionPointer, int1, int2, int3, int4) (aFunctionPointer)(int1, int2, int3, int4)'>
+ 	"To write the FFI call failure code we simulate invoking the production VM's
+ 	 fatal exception handlers (sigsegv on Unix, squeakExceptionHandler on WIN32, et al)."
+ 	^[self perform: aFunctionPointer
+ 			with: int1
+ 			with: int2
+ 			with: int3
+ 			with: int4]
+ 		on: Error
+ 		do: [:ex|
+ 			interpreterProxy
+ 				primitiveFailForFFIException: PrimErrFFIException at: aFunctionPointer asInteger;
+ 				activateFailingPrimitiveMethod]!
- 	^self 
- 		perform: aFunctionPointer
- 		with: int1
- 		with: int2
- 		with: int3
- 		with: int4!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>dispatchFunctionPointer:with:with:with:with:with:with: (in category 'callout support') -----
  dispatchFunctionPointer: aFunctionPointer with: int1 with: int2 with: int3 with: int4 with: int5 with: int6
+ 	"In C aFunctionPointer is void (*aFunctionPointer)(int, int, int, int, int, int)"
+ 	<cmacro: '(aFunctionPointer, int1, int2, int3, int4) (aFunctionPointer)(int1, int2, int3, int4, int5, int6)'>
+ 	"To write the FFI call failure code we simulate invoking the production VM's
+ 	 fatal exception handlers (sigsegv on Unix, squeakExceptionHandler on WIN32, et al)."
+ 	^[self perform: aFunctionPointer
+ 			with: int1
+ 			with: int2
+ 			with: int3
+ 			with: int4
+ 			with: int5
+ 			with: int6]
+ 		on: Error
+ 		do: [:ex|
+ 			interpreterProxy
+ 				primitiveFailForFFIException: PrimErrFFIException at: aFunctionPointer asInteger;
+ 				activateFailingPrimitiveMethod]!
- 	"In C aFunctionPointer is void (*aFunctionPointer)(int, int, int, int)"
- 	<cmacro: '(aFunctionPointer,a1,a2, a3, a4,a5,a6) (aFunctionPointer)(a1,a2, a3, a4,a5,a6)'>
- 	^self 
- 		perform: aFunctionPointer
- 		with: int1
- 		with: int2
- 		with: int3
- 		with: int4
- 		with: int5
- 		with: int6!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>initialiseModule (in category 'initialize') -----
  initialiseModule
  	<export: true>
+ 	ffiLastError := 0.
  	"By default, disable logging"
  	ffiLogEnabled := false.
  	"Get the instSize of ExternalFunction to know whether it contains a cache of the stackSize,
  	 and what the offset of ExternalLibraryFunction's functionName and moduleName slots are."
  	externalFunctionInstSize := interpreterProxy instanceSizeOf: interpreterProxy classExternalFunction.
  	self initSurfacePluginFunctionPointers.
  	^true!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>morphIntoConcreteSubclass: (in category 'simulation') -----
  morphIntoConcreteSubclass: aCoInterpreter
  	<doNotGenerate>
  	| concreteClass |
  	concreteClass :=
  		aCoInterpreter ISA caseOf: {
  			[#X64]		->	[(Smalltalk platformName beginsWith: 'Win')
  								ifTrue: [ThreadedX64Win64FFIPlugin]
  								ifFalse: [ThreadedX64SysVFFIPlugin]].
  			[#IA32]	->	[ThreadedIA32FFIPlugin].
  			[#ARMv5]	->	[ThreadedARMFFIPlugin] }
  			otherwise: [self error: 'simulation not set up for this ISA'].
+ 	"If the concreteClass has an initialize method, other than ThreadedFFIPlugin class>>initialize
+ 	 then it needs to be run."
+ 	((concreteClass class whichClassIncludesSelector: #initialize) inheritsFrom: self class class) ifTrue:
+ 		[concreteClass initialize].
+ 	concreteClass adoptInstance: self!
- 	self changeClassTo: concreteClass!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIGetLastError (in category 'primitives') -----
  primitiveFFIGetLastError
  	"Primitive. Return the error code from a failed call to the foreign function interface.
  	 This is for backwards-compatibility.  Thread-safe access to the error code is via the
  	 primitive error code."
  	<export: true>
  	<inline: false>
+ 	interpreterProxy methodReturnInteger: ffiLastError!
- 	interpreterProxy pop: 1.
- 	^interpreterProxy pushInteger: ffiLastError!

Item was changed:
  SharedPool subclass: #VMBasicConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrFFIException PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN'
- 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMBasicConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for basic constants upon which the VM as a whole depends.
  
  self ensureClassPool.
  self classPool declare: #BytesPerWord from: VMSqueakV3ObjectRepresentationConstants classPool.
  self classPool declare: #BaseHeaderSize from: VMSqueakV3ObjectRepresentationConstants classPool
  (ObjectMemory classPool keys select: [:k| k beginsWith: 'Byte']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!

Item was changed:
  ----- Method: VMClass class>>initializePrimitiveErrorCodes (in category 'initialization') -----
  initializePrimitiveErrorCodes
  	"Define the VM's primitive error codes.  N.B. these are
  	 replicated in platforms/Cross/vm/sqVirtualMachine.h."
  	"VMClass initializePrimitiveErrorCodes"
  	| pet |
  	PrimErrTableIndex := 51. "Zero-relative"
  	"See SmalltalkImage>>recreateSpecialObjectsArray for the table definition.
  	 If the table exists and is large enough the corresponding entry is returned as
  	 the primitive error, otherwise the error is answered numerically."
  	pet := Smalltalk specialObjectsArray at: PrimErrTableIndex + 1 ifAbsent: [#()].
  	pet isArray ifFalse: [pet := #()].
  	PrimNoErr := 0. "for helper methods that need to answer success or an error code."
  	PrimErrGenericFailure		:= pet indexOf: nil ifAbsent: 1.
  	PrimErrBadReceiver			:= pet indexOf: #'bad receiver' ifAbsent: 2.
  	PrimErrBadArgument		:= pet indexOf: #'bad argument' ifAbsent: 3.
  	PrimErrBadIndex			:= pet indexOf: #'bad index' ifAbsent: 4.
  	PrimErrBadNumArgs		:= pet indexOf: #'bad number of arguments' ifAbsent: 5.
  	PrimErrInappropriate		:= pet indexOf: #'inappropriate operation' ifAbsent: 6.
  	PrimErrUnsupported		:= pet indexOf: #'unsupported operation' ifAbsent: 7.
  	PrimErrNoModification		:= pet indexOf: #'no modification' ifAbsent: 8.
  	PrimErrNoMemory			:= pet indexOf: #'insufficient object memory' ifAbsent: 9.
  	PrimErrNoCMemory			:= pet indexOf: #'insufficient C memory' ifAbsent: 10.
  	PrimErrNotFound			:= pet indexOf: #'not found' ifAbsent: 11.
  	PrimErrBadMethod			:= pet indexOf: #'bad method' ifAbsent: 12.
  	PrimErrNamedInternal		:= pet indexOf: #'internal error in named primitive machinery' ifAbsent: 13.
  	PrimErrObjectMayMove		:= pet indexOf: #'object may move' ifAbsent: 14.
  	PrimErrLimitExceeded		:= pet indexOf: #'resource limit exceeded' ifAbsent: 15.
  	PrimErrObjectIsPinned		:= pet indexOf: #'object is pinned' ifAbsent: 16.
  	PrimErrWritePastObject		:= pet indexOf: #'primitive write beyond end of object' ifAbsent: 17.
  	PrimErrObjectMoved		:= pet indexOf: #'object moved' ifAbsent: 18.
  	PrimErrObjectNotPinned	:= pet indexOf: #'object not pinned' ifAbsent: 19.
  	PrimErrCallbackError		:= pet indexOf: #'error in callback' ifAbsent: 20.
+ 	PrimErrOSError				:= pet indexOf: #'operating system error' ifAbsent: 21.
+ 	PrimErrFFIException		:= pet indexOf: #'ffi call exception' ifAbsent: 22!
- 	PrimErrOSError				:= pet indexOf: #'operating system error' ifAbsent: 21!

Item was changed:
  ----- Method: VMClass>>alloca: (in category 'C library simulation') -----
  alloca: size
  	"Simulation of alloca(3)"
  	<doNotGenerate>
+ 	^CArrayAccessor on: (ByteArray new: size)!
- 	^ByteArray new: size!



More information about the Vm-dev mailing list