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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 1 21:56:37 UTC 2020


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

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

Name: VMMaker.oscog-eem.2798
Author: eem
Time: 1 September 2020, 2:56:29.93321 pm
UUID: e250e397-13bb-4ced-832a-82af2d5cea11
Ancestors: VMMaker.oscog-eem.2797

Interpreters:
Clean up setjmp/longjmp.  Use only _setjmp:/_longjmp:_:.  To get Win64 working it is easier to use a setjmp/longjmp pair that does not do stack unwinding.  It is more difficult to stitch teh stack properly so that Kernel32's checking on stack unwinding does not raise an error.  So now we're using _setjmp/longjmp everywhere and can fix things on WIN32 either to to invoke longjmpex or to use a _setjmp/_longjmp replacement a la Win64.

Fix regressions in simulation :
methodReturnString: (rcvr must be objectMemory).
SoundPlugin needs snd_Stop et al.

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

Item was added:
+ ----- Method: CoInterpreter>>_longjmp:_: (in category 'cog jit support') -----
+ _longjmp: aJumpBuf _: returnValue
+ 	"Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp
+ 	 pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc.
+ 	 Signal the exception that simulates a longjmp back to the interpreter." 
+ 	<doNotGenerate>
+ 	self halt: 'This should not be encountered now we use ceInvokeInterpreter!!!!'.
+ 	(aJumpBuf == reenterInterpreter
+ 	 and: [returnValue ~= 2 "2 == returnToThreadSchedulingLoopVia:"]) ifTrue:
+ 		[self assert: (self isOnRumpCStack: cogit processor sp).
+ 		 self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: nil].
+ 	aJumpBuf returnValue: returnValue; signal!

Item was changed:
  ----- Method: CoInterpreter>>callbackEnter: (in category 'callback support') -----
  callbackEnter: callbackID
  	"Re-enter the interpreter for executing a callback"
  	| currentCStackPointer currentCFramePointer wasInMachineCode calledFromMachineCode |
  	<volatile>
  	<export: true>
  	<var: #currentCStackPointer type: #usqIntptr_t>
  	<var: #currentCFramePointer type: #usqIntptr_t>
  	<var: #callbackID type: #'sqInt *'>
  
  	"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.
  
  	wasInMachineCode := self isMachineCodeFrame: framePointer.
  	calledFromMachineCode := instructionPointer <= objectMemory startOfMemory.
  
  	"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.
  	self flag: 'need to debug this properly.  Conceptually it is the right thing to do but it crashes in practice'.
  	false
  		ifTrue:
  			["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 from: CSCallbackLeave]]
  		ifFalse:
  			[self transferTo: self wakeHighestPriority from: CSCallbackLeave].
  
  	"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 CStackPointers..."
  	currentCStackPointer := CStackPointer.
  	currentCFramePointer := CFramePointer.
  	cogit assertCStackWellAligned.
+ 	(self _setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
- 	(self setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
  		[callbackID at: 0 put: jmpDepth.
  		 self enterSmalltalkExecutive.
  		 self assert: false "NOTREACHED"].
  
  	"Restore the previous CStackPointers..."
  	self setCFramePointer: currentCFramePointer setCStackPointer: currentCStackPointer.
  
  	"Transfer back to the previous process so that caller can push result"
  	self putToSleep: self activeProcess yieldingIf: preemptionYields.
  	self transferTo: (suspendedCallbacks at: jmpDepth) from: CSCallbackLeave.
  	newMethod := suspendedMethods at: jmpDepth.	"see comment above"
  	argumentCount := self argumentCountOf: newMethod.
  	self assert: wasInMachineCode = (self isMachineCodeFrame: framePointer).
  	calledFromMachineCode
  		ifTrue:
  			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer.
  				 instructionPointer := cogit ceReturnToInterpreterPC]]
  		ifFalse:
  			["Even if the context was flushed to the heap and rebuilt in transferTo:from:
  			  above it will remain an interpreted frame because the context's pc would
  			  remain a bytecode pc.  So the instructionPointer must also be a bytecode pc."
  			 self assert: (self isMachineCodeFrame: framePointer) not.
  			 self assert: instructionPointer > objectMemory startOfMemory].
  	self assert: primFailCode = 0.
  	jmpDepth := jmpDepth-1.
  	^true!

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

Item was changed:
  ----- Method: CoInterpreterMT>>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.  Capture the C stack
  	 pointers so that calls from machine-code into the C run-time occur at this level.
  	 This is the actual implementation, separated from enterSmalltalkExecutive so the
  	 simulator can wrap it in an exception handler and hence simulate the setjmp/longjmp.
  
  	 Override to return if a longjmp to reenterInterpreter passes a parameter greater than 1.
  	 This causes a return to threadSchedulingLoop:startingVM: and is used to surrender
  	 control to another thread."
  	<inline: false>
  	self assertSaneThreadAndProcess.
  	cogit assertCStackWellAligned.
  	cogit ceCaptureCStackPointers.
  	"Setjmp for reentry into interpreter from elsewhere, e.g. machine-code trampolines."
+ 	(self _setjmp: reenterInterpreter) > 1 ifTrue:
- 	(self sigset: reenterInterpreter jmp: 0) > 1 ifTrue:
  		[^0].
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self returnToExecutive: false postContextSwitch: true
  		 "NOTREACHED"].
  	self setMethod: (self iframeMethod: framePointer).
  	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  		[instructionPointer := self iframeSavedIP: framePointer].
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self interpret.
  	"NOTREACHED"
  	^0!

Item was changed:
  ----- Method: CoInterpreterMT>>returnToSchedulingLoopAndReleaseVMOrWakeThread:source: (in category 'process primitive support') -----
  returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: source
  	| savedReenterInterpreter |
  	<var: #savedReenterInterpreter type: #'jmp_buf'>
  	<var: #vmThread type: #'CogVMThread *'>
  	<inline: false>
  	self cCode:
  			[self flag: 'this is just for debugging.  Note the current C stack pointers'.
  			 cogThreadManager currentVMThread
  				cStackPointer: CStackPointer;
  				cFramePointer: CFramePointer]
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: cogThreadManager getVMOwner.
  			 self assert: (range includes: CStackPointer).
  			 self assert: (range includes: CFramePointer)].
  	"We must use a copy of reenterInterpreter since we're giving up the VM to another vmThread."
  	self cCode:
  			[self memcpy: savedReenterInterpreter asVoidPointer
  				_: reenterInterpreter
  				_: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[savedReenterInterpreter := reenterInterpreter].
  	self recordThreadSwitchTo: (vmThread ifNotNil: [vmThread index] ifNil: [0]) source: source.
  	vmThread
  		ifNotNil: [cogThreadManager wakeVMThreadFor: vmThread index]
  		ifNil: [cogThreadManager releaseVM].
  	"2 implies returning to the threadSchedulingLoop."
+ 	self _longjmp: savedReenterInterpreter _: ReturnToThreadSchedulingLoop!
- 	self siglong: savedReenterInterpreter jmp: ReturnToThreadSchedulingLoop!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>cReturnAddressAddress (in category 'accessing') -----
+ cReturnAddressAddress
+ 	^self addressForLabel: #CReturnAddress!

Item was changed:
  ----- Method: Interpreter>>callbackEnter: (in category 'callback support') -----
  callbackEnter: callbackID
  	"Re-enter the interpreter for executing a callback"
  	| result activeProc |
  	<export: true>
  	<var: #callbackID declareC: 'sqInt *callbackID'>
  
  	"For now, do not allow a callback unless we're in a primitiveResponse"
  	primitiveIndex = 0 ifTrue:[^false].
  
  	"Check if we've exceeded the callback depth"
  	jmpDepth >= jmpMax ifTrue:[^false].
  	jmpDepth := jmpDepth + 1.
  
  	"Suspend the currently active process"
  	activeProc := self fetchPointer: ActiveProcessIndex
  						 ofObject: self schedulerPointer.
  	suspendedCallbacks at: jmpDepth put: activeProc.
  	"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.
  	self transferTo: self wakeHighestPriority.
  
  	"Typically, invoking the callback means that some semaphore has been 
  	signaled to indicate the callback. Force an interrupt check right away."
  	self forceInterruptCheck.
  
+ 	result := self _setjmp: (jmpBuf at: jmpDepth).
- 	result := self setjmp: (jmpBuf at: jmpDepth).
  	result == 0 ifTrue:["Fill in callbackID"
  		callbackID at: 0 put: jmpDepth.
  		"This is ugly but the inliner treats interpret() in very special and strange ways and calling any kind of 'self interpret' either directly or even via cCode:inSmalltalk: will cause this entire method to vanish."
  		self cCode: 'interpret()'.
  	].
  
  	"Transfer back to the previous process so that caller can push result"
  	activeProc := self fetchPointer: ActiveProcessIndex
  						 ofObject: self schedulerPointer.
  	self putToSleep: activeProc.
  	activeProc := suspendedCallbacks at: jmpDepth.
  	newMethod := suspendedMethods at: jmpDepth.	"see comment above"
  	self transferTo: activeProc.
  	jmpDepth := jmpDepth-1.
  	^true!

Item was changed:
  ----- Method: Interpreter>>callbackLeave: (in category 'callback support') -----
  callbackLeave: cbID
  	"Leave from a previous callback"
  	<export: true>
  
  	"For now, do not allow a callback unless we're in a primitiveResponse"
  	primitiveIndex = 0 ifTrue:[^false].
  
  	"Check if this is the top-level callback"
  	cbID = jmpDepth ifFalse:[^false].
  	cbID < 1 ifTrue:[^false].
  
  	"Pop the arguments of the return primitive"
  	self pop: argumentCount.
  
  	"This is ugly but necessary, or otherwise the Mac will not build"
+ 	self _longjmp: (jmpBuf at: jmpDepth) _: 1.
- 	self long: (jmpBuf at: jmpDepth) jmp: 1.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: SoundPlugin>>initialiseModule (in category 'initialize-release') -----
  initialiseModule
  	<export: true>
+ 	^self soundInit!
- 	^self cCode: 'soundInit()' inSmalltalk:[true]!

Item was changed:
  ----- Method: SoundPlugin>>shutdownModule (in category 'initialize-release') -----
  shutdownModule
  	<export: true>
+ 	^self soundShutdown!
- 	^self cCode: 'soundShutdown()' inSmalltalk:[true]!

Item was added:
+ ----- Method: SoundPlugin>>snd_Stop (in category 'simulation') -----
+ snd_Stop
+ 	<doNotGenerate>!

Item was added:
+ ----- Method: SoundPlugin>>soundInit (in category 'simulation') -----
+ soundInit
+ 	<doNotGenerate>
+ 	^true!

Item was added:
+ ----- Method: SoundPlugin>>soundShutdown (in category 'simulation') -----
+ soundShutdown
+ 	<doNotGenerate>
+ 	^true!

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: '"sqSetjmpShim.h"';
+ 		addHeaderFile: '"dispdbg.h"'.
+ 	LowcodeVM ifTrue:
+ 		[aCCodeGenerator addHeaderFile: '"sqLowcodeFFI.h"'].
- 		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: #usqLong. "see dispdbg.h"
- 		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 type: 'jmp_buf'.
  	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]].
  		
  	aCCodeGenerator
  		var: #primitiveDoMixedArithmetic
  		declareC: 'char primitiveDoMixedArithmetic = 1'.!

Item was changed:
  ----- Method: StackInterpreter class>>preambleCCode (in category 'translation') -----
  preambleCCode
  	^	
  '/* Disable Intel compiler inlining of warning which is used for breakpoints */
  #pragma auto_inline(off)
  sqInt warnpid, erroronwarn;
  EXPORT(void)
  warning(char *s) { /* Print an error message but don''t necessarily exit. */
  	if (erroronwarn) error(s);
  	if (warnpid)
  		printf("\n%s pid %ld\n", s, (long)warnpid);
  	else
  		printf("\n%s\n", s);
  }
  EXPORT(void)
  warningat(char *s, int l) { /* ditto with line number. */
  	/* use alloca to call warning so one does not have to remember to set two breakpoints... */
  	char *sl = alloca(strlen(s) + 16);
  	sprintf(sl, "%s %d", s, l);
  	warning(sl);
  }
  #pragma auto_inline(on)
- 
- /*
-  * Define sigsetjmp and siglongjmp to be the most minimal setjmp/longjmp available on the platform.
-  * Note: on windows 64 via mingw-w64, the 2nd argument NULL to _setjmp prevents stack unwinding
-  * On windows 32 via MSVC _longjmpex prevents stack unwinding. Not supported on windows 64.
-  */
- #undef sigsetjmp
- #undef siglongjmp
- #if _MSC_VER
- # if _WIN64
- #	define sigsetjmp(jb,ssmf) _setjmp(jb)
- #	define siglongjmp(jb,v) longjmp(jb,v)
- # else
- #	define sigsetjmp(jb,ssmf) _setjmp(jb)
- #	define siglongjmp(jb,v) _longjmpex(jb,v)
- # endif
- #elif _WIN64 && __GNUC__
- # define sigsetjmp(jb,ssmf) _setjmp(jb,NULL)
- # define siglongjmp(jb,v) longjmp(jb,v)
- #elif _WIN32
- # define sigsetjmp(jb,ssmf) setjmp(jb)
- # define siglongjmp(jb,v) longjmp(jb,v)
- #else
- # define sigsetjmp(jb,ssmf) _setjmp(jb)
- # define siglongjmp(jb,v) _longjmp(jb,v)
- #endif
- 
- #define odd(v) ((int)(v)&1)
- #define even(v) (!!odd(v))
  '!

Item was added:
+ ----- Method: StackInterpreter>>_longjmp:_: (in category 'simulation') -----
+ _longjmp: aJumpBuf _: returnValue
+ 	"Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp
+ 	 pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc.
+ 	 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 added:
+ ----- Method: StackInterpreter>>_setjmp: (in category 'primitive support') -----
+ _setjmp: aJumpBuf
+ 	"Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp
+ 	 pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc.
+ 	 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>>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)."
  	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 _longjmp: reenterInterpreter _: ReturnToInterpreter.
- 	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  	"NOTREACHED"
  	^nil!

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>
  	<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 memcpy: savedReenterInterpreter asVoidPointer
  		_: reenterInterpreter
  		_: (self sizeof: #'jmp_buf').
+ 	(self _setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
- 	(self setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
  		[callbackID at: 0 put: jmpDepth.
  		 self enterSmalltalkExecutive.
  		 self assert: false "NOTREACHED"].
  
  	"Restore the previous interpreter entry jmp_buf."
  	self memcpy: reenterInterpreter
  		_: (self cCoerceSimple: savedReenterInterpreter to: #'void *')
  		_: (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.
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>callbackLeave: (in category 'callback support') -----
  callbackLeave: cbID
  	"Leave from a previous callback"
  	<export: true>
  
  	"For now, do not allow a callback return unless we're in a primitiveResponse"
  	(self asserta: primitiveFunctionPointer ~= 0) ifFalse:
  		[^false].
  
  	"Check if this is the top-level callback"
  	cbID = jmpDepth ifFalse:[^false].
  	cbID < 1 ifTrue:[^false].
  	"This is ugly but necessary, or otherwise the Mac will not build"
+ 	self _longjmp: (jmpBuf at: jmpDepth) _: 1.
- 	self long: (jmpBuf at: jmpDepth) jmp: 1.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- 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 _setjmp: reenterInterpreter.
- 	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 removed:
- ----- 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>>methodReturnString: (in category 'plugin primitive support') -----
  methodReturnString: aCString
  	"Attempt to answer a ByteString for a given C string as the result of a primitive."
  	<var: 'aCString' type: #'char *'>
  	self deny: self failed.
  	aCString
  		ifNil: [primFailCode := PrimErrOperationFailed]
  		ifNotNil:
+ 			[(objectMemory stringForCString: aCString)
- 			[(self stringForCString: aCString)
  				ifNil: [primFailCode := PrimErrNoMemory]
  				ifNotNil: [:result| self pop: argumentCount+1 thenPush: result]].
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>returnAs:ThroughCallback:Context: (in category 'callback support') -----
  returnAs: returnTypeOop ThroughCallback: vmCallbackContext Context: callbackMethodContext
  	"callbackMethodContext is an activation of invokeCallback:[stack:registers:jmpbuf:].
  	 Its sender is the VM's state prior to the callback.  Reestablish that state (via longjmp),
  	 and mark callbackMethodContext as dead."
  	<export: true>
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	| calloutMethodContext theFP thePage |
  	<var: #theFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	self assert: primFailCode = 0.
  	self assert: (objectMemory isIntegerObject: returnTypeOop).
  	self assert: (objectMemory isImmediate: vmCallbackContext asInteger) not.
  	self assert: ((objectMemory addressCouldBeObj: callbackMethodContext)
  				and: [objectMemory isContext: callbackMethodContext]).
  	self assert: (debugCallbackPath := 0) = 0.
  	((objectMemory isIntegerObject: returnTypeOop)
  	 and: [self isLiveContext: callbackMethodContext]) ifFalse:
  		[self assert: (debugCallbackPath := 1) = 1.
  		 ^false].
  	calloutMethodContext := self externalInstVar: SenderIndex ofContext: callbackMethodContext.
  	(self isLiveContext: calloutMethodContext) ifFalse:
  		[self assert: (debugCallbackPath := 2) = 2.
  		 ^false].
  	self assert: (debugCallbackReturns := debugCallbackReturns + 1) > 0.
  	"self assert: debugCallbackReturns < 3802."
  	"We're about to leave this stack page; must save the current frame's instructionPointer."
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	"Mark callbackMethodContext as dead; the common case is that it is the current frame.
  	 We go the extra mile for the debugger."
  	(self isSingleContext: callbackMethodContext)
  		ifTrue:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 4) > 0.
  		 	 self markContextAsDead: callbackMethodContext]
  		ifFalse:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 8) > 0.
  		 	 theFP := self frameOfMarriedContext: callbackMethodContext.
  			 self assert: (self frameReceiver: theFP) = (objectMemory splObj: ClassAlien).
  			 framePointer = theFP "common case"
  				ifTrue:
  					[self assert: (debugCallbackPath := debugCallbackPath bitOr: 16) > 0.
  		 			 (self isBaseFrame: theFP) ifFalse: "calloutMethodContext is immediately below on the same page.  Make it current."
  						[self assert: (debugCallbackPath := debugCallbackPath bitOr: 32) > 0.
  		 				 instructionPointer := (self frameCallerSavedIP: theFP) asUnsignedInteger.
  						 stackPointer := theFP + (self frameStackedReceiverOffset: theFP) + objectMemory wordSize.
  						 framePointer := self frameCallerFP: theFP.
  						 self setMethod: (self frameMethodObject: framePointer).
  						 self restoreCStackStateForCallbackContext: vmCallbackContext.
  						 self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  						 "N.B. siglongjmp is defines as _longjmp on non-win32 platforms.
  						  This matches the use of _setjmp in ia32abicc.c."
+ 						 self _longjmp: vmCallbackContext trampoline _: (self integerValueOf: returnTypeOop).
- 						 self siglong: vmCallbackContext trampoline jmp: (self integerValueOf: returnTypeOop).
  						 ^true].
  					 stackPages freeStackPage: stackPage]
  				ifFalse:
  					[self assert: (debugCallbackPath := debugCallbackPath bitOr: 64) > 0.
  		 			 self externalDivorceFrame: theFP andContext: callbackMethodContext.
  					 self markContextAsDead: callbackMethodContext]].
  	"Make the calloutMethodContext the active frame.  The case where calloutMethodContext
  	 is immediately below callbackMethodContext on the same page is handled above."
  	(self isStillMarriedContext: calloutMethodContext)
  		ifTrue:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 128) > 0.
  		 	 theFP := self frameOfMarriedContext: calloutMethodContext.
  			 thePage := stackPages stackPageFor: theFP.
  			 "findSPOf:on: points to the word beneath the instructionPointer, but
  			  there is no instructionPointer on the top frame of the current page."
  			 self assert: thePage ~= stackPage.
  			 stackPointer := thePage headFP = theFP
  								ifTrue: [thePage headSP]
  								ifFalse: [(self findSPOf: theFP on: thePage) - objectMemory wordSize].
  			 framePointer := theFP.
  			 self assert: stackPointer < framePointer]
  		ifFalse:
  			[self assert: (debugCallbackPath := debugCallbackPath bitOr: 256) > 0.
  		 	 thePage := self makeBaseFrameFor: calloutMethodContext.
  			 self setStackPointersFromPage: thePage].
  	instructionPointer := self popStack.
  	self setMethod: (objectMemory fetchPointer: MethodIndex ofObject: calloutMethodContext).
  	self setStackPageAndLimit: thePage.
  	self restoreCStackStateForCallbackContext: vmCallbackContext.
  	primitiveFunctionPointer := vmCallbackContext savedPrimFunctionPointer.
  	"N.B. siglongjmp is defined as _longjmp on non-win32 platforms.
  	  This matches the use of _setjmp in ia32abicc.c."
+ 	self _longjmp: vmCallbackContext trampoline _: (self integerValueOf: returnTypeOop).
- 	self siglong: vmCallbackContext trampoline jmp: (self integerValueOf: returnTypeOop).
  	"NOTREACHED"
  	^true!

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

Item was removed:
- ----- 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!



More information about the Vm-dev mailing list