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

commits at source.squeak.org commits at source.squeak.org
Mon Apr 27 21:23:08 UTC 2020


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

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

Name: VMMaker.oscog-eem.2748
Author: eem
Time: 27 April 2020, 2:22:49.428028 pm
UUID: 76ab3da9-b0d6-4c09-9d55-9ac9d70f5ec3
Ancestors: VMMaker.oscog-eem.2747

Plugins: Add error to the VM proxy API, deleting obsoleteDontUseThisFetchWord:ofObject:. obsoleteDontUseThisFetchWord:ofObject: has never been used by a Cog/Stack VM plugin, and no plugin has sent erro up until now, so this is a safe repurpose of an unused slot.

Have BalloonEngineBase>>errorWrongIndex use the VM proxy API's error.

Slang: clean-up shouldGenerateAsInterpreterProxySend:, implementing it simply in CCodeGenerator and overriding in VMPluginCodeGenerator.  Hence nuke messageReceiverIsInterpreterProxy:.

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

Item was changed:
  ----- Method: BalloonEngineBase>>errorWrongIndex (in category 'private') -----
  errorWrongIndex
+ 	interpreterProxy error:'BalloonEngine: Fatal dispatch error'!
- 	"Ignore dispatch errors when translating to C
- 	(since we have no entry point for #error in the VM proxy)"
- 	self cCode:'' inSmalltalk:[self error:'BalloonEngine: Fatal dispatch error']!

Item was removed:
- ----- Method: BalloonEngineSimulation>>assert: (in category 'simulation') -----
- assert: aBoolean
- 	aBoolean ifFalse:[^self error:'Assertion failed'].!

Item was removed:
- ----- Method: CCodeGenerator>>messageReceiverIsInterpreterProxy: (in category 'utilities') -----
- messageReceiverIsInterpreterProxy: sendNode
- 	^self isGeneratingPluginCode
- 	  and: [sendNode receiver isVariable
- 	  and: ['interpreterProxy' = sendNode receiver name
- 	  and: [(self isKernelSelector: sendNode selector) not]]]!

Item was changed:
  ----- Method: CCodeGenerator>>shouldGenerateAsInterpreterProxySend: (in category 'utilities') -----
  shouldGenerateAsInterpreterProxySend: aSendNode
+ 	^false!
- 	^(self messageReceiverIsInterpreterProxy: aSendNode)
- 	  and: [(VMBasicConstants mostBasicConstantSelectors includes: aSendNode selector) not]!

Item was changed:
  ----- Method: IA32ABIPlugin>>primAllocateExecutablePage (in category 'primitives-memory management') -----
  primAllocateExecutablePage
  	"Answer an Alien for an executable page; for thunks"
  	"primAllocateExecutablePage ^<Alien>
  		<primitive: 'primAllocateExecutablePage' error: errorCode module: 'IA32ABI'>"
  	| byteSize ptr mem alien |
  	<export: true>
  	<var: #byteSize type: #'sqIntptr_t'>
  	<var: #ptr type: #'sqIntptr_t *'>
  	<var: #mem type: #'void *'>
  
+ 	mem := self allocateExecutablePage: (self addressOf: byteSize put: [:v| byteSize := v]).
- 	self cCode: 'mem = allocateExecutablePage(&byteSize)'
- 		inSmalltalk: [self error: 'not yet implemented'. mem := 0. byteSize := 0].
  	mem = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
  	alien := interpreterProxy
  				instantiateClass: interpreterProxy classAlien
  				indexableSize: 2 * interpreterProxy bytesPerOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	ptr := interpreterProxy firstIndexableField: alien.
  	ptr at: 0 put: 0 - byteSize. "indirect mem indicated by negative size. Slang doesn't grok negated"
  	ptr at: 1 put: (self cCoerce: mem to: #'sqIntptr_t').
  	interpreterProxy methodReturnValue: alien!

Item was added:
+ ----- Method: IA32ABIPluginSimulator>>allocateExecutablePage: (in category 'platform support') -----
+ allocateExecutablePage: byteSizePtrBlock
+ 	"void *allocateExecutablePage(sqIntptr_t *byteSizePtrBlock)"
+ 	self error: 'not yet implemented'.
+ 	byteSizePtrBlock value: 0.
+ 	^0!

Item was added:
+ ----- Method: InterpreterProxy>>error: (in category 'other') -----
+ error: aString
+ 	<returnTypeC: #void>
+ 	<var: 'aString' type: #'char *'>
+ 	"In the real VM this prints aString to stderr and then calls exit(-1) or abort()."
+ 	^super error: aString!

Item was removed:
- ----- Method: InterpreterProxy>>obsoleteDontUseThisFetchWord:ofObject: (in category 'object access') -----
- obsoleteDontUseThisFetchWord: fieldIndex ofObject: oop
- "fetchWord:ofObject: is rescinded as of VMMaker 3.8 64bit VM. This is a placeholder to sit in the sqVirtualMachine structure to support older plugins for a while"
- 	self halt: 'deprecated method'!

Item was removed:
- ----- Method: ObjectMemory>>obsoleteDontUseThisFetchWord:ofObject: (in category 'interpreter access') -----
- obsoleteDontUseThisFetchWord: fieldIndex ofObject: oop
- 	"This message is deprecated but supported for a while via a tweak to sqVirtualMachine.[ch] Use fetchLong32, fetchLong64 or fetchPointer instead for new code"
- 
- 	^self fetchLong32: fieldIndex ofObject: oop!

Item was removed:
- ----- Method: SmartSyntaxInterpreterPlugin>>sqAssert: (in category 'debugging') -----
- sqAssert: aBool 
- 	self debugCode:
- 		[aBool ifFalse:
- 			[self error: 'Assertion failed!!']].
- 	^aBool!

Item was removed:
- ----- Method: SpurMemoryManager>>obsoleteDontUseThisFetchWord:ofObject: (in category 'plugin support') -----
- obsoleteDontUseThisFetchWord: fieldIndex ofObject: oop
- 	"This message is deprecated but supported for a while via a tweak to sqVirtualMachine.[ch] Use fetchLong32, fetchLong64 or fetchPointer instead for new code"
- 	<api>
- 	^self fetchLong32: fieldIndex ofObject: oop!

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]	->	[ThreadedARM32FFIPlugin].
+ 			[#ARMv8]	->	[ThreadedARM64FFIPlugin] }
- 			[#ARMv5]	->	[ThreadedARM32FFIPlugin] }
  			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!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>shouldGenerateAsInterpreterProxySend: (in category 'utilities') -----
+ shouldGenerateAsInterpreterProxySend: aSendNode
+ 	"Answer if this send should be generated as interpreterProxy->foo or its moral equivalent (*).
+ 	 (*) since we now use function pointers declared in each external plugin we only indirect through
+ 	 interopreterProxy at plugin initialization.  But we still have to find the set of sends a plugin uses."
+ 	| selector |
+ 	(aSendNode receiver isVariable and: ['interpreterProxy' = aSendNode receiver name]) ifFalse: [^false].
+ 	selector := aSendNode selector.
+ 	"baseHeaderSize, minSmallInteger et al are #defined in each VM's interp.h"
+ 	(VMBasicConstants mostBasicConstantSelectors includes: selector) ifTrue: [^false].
+ 	"Only include genuine InterpreterProxy methods, excluding things not understood
+ 	 by InterpreterProxy and things in its initialize and private protocols."
+ 	^(#(initialize private) includes: (InterpreterProxy compiledMethodAt: selector ifAbsent: [^false]) protocol) not!



More information about the Vm-dev mailing list