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

commits at source.squeak.org commits at source.squeak.org
Mon Oct 19 17:28:34 UTC 2020


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

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

Name: VMMaker.oscog-eem.2850
Author: eem
Time: 19 October 2020, 10:28:25.094321 am
UUID: 4d7fc8a4-2c7d-4bad-8aeb-5f8c5766e12a
Ancestors: VMMaker.oscog-eem.2849

Have the interpreters include sqImageFileAccess.h directly so that sq.h doesn't have to, and hence the entire VM isn't recompiled whenever sqImageFileAccess.h does.

Fix some C compiler warnings around invalidCompactClassError:.

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

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

Item was changed:
  ----- Method: ObjectMemory>>invalidCompactClassError: (in category 'initialization') -----
  invalidCompactClassError: className
+ 	<var: 'className' type: #'const char *'>
  	<inline: false>
  	self cCode:
  			['\nClass %s does not have the required compact class index\n' printf: className.
  			 self exit: -1]
  		inSmalltalk:
  			[self error: 'Class ', className, ' does not have the required compact class index']!

Item was changed:
  ----- Method: SpurMemoryManager>>invalidCompactClassError: (in category 'initialization') -----
  invalidCompactClassError: className
+ 	<var: 'className' type: #'const char *'>
  	<inline: false>
  	self cCode:
  			['\nClass %s does not have the required class index\n' printf: className.
  			 self exit: -1]
  		inSmalltalk:
  			[self error: 'Class ', className, ' does not have the required class index']!

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: '<stdio.h> /* for printf */';
  		addHeaderFile: '<stdlib.h> /* for e.g. alloca */';
  		addHeaderFile: '<setjmp.h>';
  		addHeaderFile: '<wchar.h> /* for wint_t */';
  		addHeaderFile: '"vmCallback.h"';
  		addHeaderFile: '"sqMemoryFence.h"';
+ 		addHeaderFile: '"sqImageFileAccess.h"';
  		addHeaderFile: '"sqSetjmpShim.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"
  	"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'.!



More information about the Vm-dev mailing list