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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 28 17:53:53 UTC 2021


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

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

Name: VMMaker.oscog-eem.3076
Author: eem
Time: 28 September 2021, 10:53:41.911915 am
UUID: ebca036d-ae29-45f9-b768-65766ee8164e
Ancestors: VMMaker.oscog-eem.3075

Add primitiveFailFor:withSecondary: to allow the ThreadedFFIPlugin to fail with the new PrimErrFFIMarshallingError and its own specific marshalling error code as a parameter.

StackInterpreter: make sure primitiveCallout is loaded only once from SqueakFFIPrims.  C initializer semantics may have meant it was being reloaded every time.

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

Item was changed:
  Object subclass: #InterpreterProxy
+ 	instanceVariableNames: 'primFailCode remapBuffer stack method argumentCount bb thisSessionID secondaryErrorCode exceptionPC'
- 	instanceVariableNames: 'primFailCode remapBuffer stack method argumentCount bb thisSessionID osErrorCode exceptionPC'
  	classVariableNames: ''
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-InterpreterSimulation'!
  
  !InterpreterProxy commentStamp: 'eem 8/24/2018 15:43' prior: 0!
  This class should provide the definition of what interpreter support plugins need and can have access to. Note that the proxy related files platforms - Cross - vm - sqVirtualMachine.[ch] are kept under the git tree at http://www.github.com/opensmalltalk/vm.
  The main use of the class is to support the vm simulator and the RSqueak VM, which implements as many primitives as possible in Smalltalk.!

Item was added:
+ ----- Method: InterpreterProxy>>primitiveFailFor:withSecondary: (in category 'other') -----
+ primitiveFailFor: reasonCode withSecondary: extraErrorCode
+ 	<var: 'extraErrorCode' type: #sqLong>
+ 	<option: #(atLeastVMProxyMajor:minor: 1 14)>
+ 	"Set primFailCode primitive failure and associated secondaryErrorCode.
+ 	 Primitive 255 is called to indicate that we are currently simulating a primitive that should fail and the VM should handle that case appropriately (if supported by the VM)."
+ 	<primitive: 255>
+ 	secondaryErrorCode := extraErrorCode.
+ 	^primFailCode := reasonCode!

Item was changed:
  ----- Method: InterpreterProxy>>primitiveFailForFFIException:at: (in category 'other') -----
  primitiveFailForFFIException: exceptionCode at: pc
  	<var: 'exceptionCode' type: #usqLong>
  	<var: 'pc' type: #usqInt>
  	<option: #(atLeastVMProxyMajor:minor: 1 14)>
  	"Set PrimErrFFIException primitive failure and associated exceptionCode (a.k.a. 
  	 osErrorCode) and exceptionPC."
  	<primitive: 255>
+ 	secondaryErrorCode := exceptionCode.
- 	osErrorCode := exceptionCode.
  	exceptionPC := pc.
  	^primFailCode := PrimErrFFIException!

Item was changed:
  ----- Method: InterpreterProxy>>primitiveFailForOSError: (in category 'other') -----
+ primitiveFailForOSError: osErrorCode
+ 	<var: 'osErrorCode' type: #sqLong>
- primitiveFailForOSError: osError
- 	<var: 'osError' type: #sqLong>
  	<option: #(atLeastVMProxyMajor:minor: 1 14)>
+ 	"Set PrimErrOSError primitive failure and associated secondaryErrorCode.
- 	"Set PrimErrOSError primitive failure and associated osErrorCode.
  	 Primitive 255 is called to indicate that we are currently simulating a primitive that should fail and the VM should handle that case appropriately (if supported by the VM)."
  	<primitive: 255>
+ 	secondaryErrorCode := osErrorCode.
- 	osErrorCode := osError.
  	^primFailCode := PrimErrOSError!

Item was added:
+ ----- Method: NewObjectMemory>>primitiveFailFor:withSecondary: (in category 'as yet unclassified') -----
+ primitiveFailFor: reasonCode withSecondary: extraErrorCode
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter primitiveFailFor: reasonCode withSecondary: extraErrorCode!

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

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

Item was added:
+ ----- Method: StackInterpreter>>cloneErrorObj: (in category 'message sending') -----
+ cloneErrorObj: errObj
+ 	"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 secondaryErrorCode,
+ 	  and if an PrimErrFFIException, then the third slow with the exceptionPC."
+ 	| numSlots clone |
+ 	<inline: true>
+ 	numSlots := objectMemory numSlotsOf: errObj.
+ 	clone := objectMemory hasSpurMemoryManagerAPI
+ 				ifTrue: [objectMemory
+ 							eeInstantiateAnySmallClassIndex: (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: (self cCoerceSimple: secondaryErrorCode to: #usqLong));
+ 				storePointerUnchecked: 2
+ 					ofObject: clone
+ 						withValue: (self positiveMachineIntegerFor: exceptionPC)]
+ 		ifFalse:
+ 			[objectMemory
+ 				storePointerUnchecked: 1
+ 				ofObject: clone
+ 				withValue: (self signed64BitIntegerFor: secondaryErrorCode)].
+ 	^clone!

Item was removed:
- ----- 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."
- 	| clone |
- 	<inline: true>
- 	clone := objectMemory hasSpurMemoryManagerAPI
- 				ifTrue: [objectMemory
- 							eeInstantiateAnySmallClassIndex: (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: (self cCoerceSimple: osErrorCode to: #usqLong));
- 				storePointerUnchecked: 2
- 					ofObject: clone
- 						withValue: (self positiveMachineIntegerFor: exceptionPC)]
- 		ifFalse:
- 			[objectMemory
- 				storePointerUnchecked: 1
- 				ofObject: clone
- 				withValue: (self signed64BitIntegerFor: osErrorCode)].
- 	^clone!

Item was changed:
  ----- Method: StackInterpreter>>functionForPrimitiveCallout (in category 'plugin primitive support') -----
  functionForPrimitiveCallout
  	"Answer the function primitiveCallout from the FFI plugin or nil if it can't
  	 be found.  Cache it for performance.  We use this circumlocution so that
  	 Squeak can be deployed without the FFI plugin for security reasons."
  
  	<returnTypeC: 'void (*functionForPrimitiveCallout())(void)'>
+ 	<inline: true>
+ 	primitiveCalloutPointer asInteger = -1 ifTrue:
+ 		[primitiveCalloutPointer := self ioLoadFunction: 'primitiveCallout' From: 'SqueakFFIPrims'].
+ 	^self cCoerceSimple: primitiveCalloutPointer to: #'void (*)(void)'!
- 	| function |
- 	<var: #function declareC: 'static void *function = (void *)-1'>
- 	self cCode: '' inSmalltalk: [function := -1].
- 	function asInteger = -1 ifTrue:
- 		[function := self ioLoadFunction: 'primitiveCallout' From: 'SqueakFFIPrims'].
- 	^self cCoerceSimple: function to: #'void (*)(void)'!

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 |
- 	| table errObj numSlots |
  	primFailCode > 0 ifTrue:
  		[table := objectMemory splObj: PrimErrTableIndex.
  		 primFailCode <= (objectMemory numSlotsOf: table) ifTrue:
  			[errObj := objectMemory followField: primFailCode - 1 ofObject: table.
+ 			 "If 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 secondaryErrorCode."
+ 			 (objectMemory formatOf: errObj) = objectMemory nonIndexablePointerFormat ifTrue:
+ 				[errObj := self cloneErrorObj: errObj].
- 			 "If this is a PrimErrOSError/PrimErrFFIException 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])
- 			  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: ThreadedFFIPlugin>>ffiFail: (in category 'callout support') -----
  ffiFail: reason
  	<inline: false>
  	"Map the FFI error code into a primitive error code.  If reason is negative it encodes one of the
  	 standard PrimErr... codes, negated to distinguish it from the FFIError codes.  If it is an FFIError...
  	 code then add the size of the primitive error table + 2 to disambiguate it from the PrimErr... codes.
  	 For historic reasons the FFIError codes range from -1 on up hence adding size + 2 maps them to
  	 size of table + 1 on up.  This OFFSET IS undone by ExternalFunction class>>externalCallFailedWith:.
+ 	 Thus we can communicate back both PrimErr.. and FFIError codes.  Complex but necessary.
+ 
+ 	 If a clonable PrimErrFFIMarshallingError is present in the error table then use the new scheme."
- 	 Thus we can communicate back both PrimErr.. and FFIError codes.  Complex but necessary."
  	ffiLastError := reason.
+ 	reason >= FFINoCalloutAvailable ifTrue:
+ 		[| errorTable numErrorTableSlots |
+ 		 errorTable := interpreterProxy primitiveErrorTable.
+ 		 numErrorTableSlots := interpreterProxy slotSizeOf: errorTable.
+ 		 (numErrorTableSlots >= PrimErrFFIMarshallingError
+ 		  and: [interpreterProxy isPointers: errorTable]) ifTrue:
+ 			[^interpreterProxy primitiveFailFor: PrimErrFFIMarshallingError withSecondary: reason].
+ 		^interpreterProxy primitiveFailFor: reason + 2 + numErrorTableSlots].
+ 	^interpreterProxy primitiveFailFor: reason negated!
- 	^interpreterProxy primitiveFailFor:
- 		(reason >= FFINoCalloutAvailable
- 			ifTrue: [reason + 2 + (interpreterProxy slotSizeOf: interpreterProxy primitiveErrorTable)]
- 			ifFalse: [reason negated])!

Item was changed:
  SharedPool subclass: #VMBasicConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMForFFICall DisownVMForThreading DoAssertionChecks DoExpensiveAssertionChecks FastCPrimitiveAlignForFloatsFlag FastCPrimitiveFlag GCCheckFreeSpace GCCheckImageSegment GCCheckPrimCall GCCheckShorten GCModeBecome GCModeFull GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrFFIException PrimErrFFIMarshallingError PrimErrGenericFailure PrimErrInappropriate PrimErrInternalError PrimErrLimitExceeded PrimErrNamedInternal PrimErrNeedCompaction PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrOperationFailed PrimErrUninitialized PrimEr
 rUnsupported PrimErrWritePastObject PrimNoErr PrimNumberHandlerMarker PrimNumberNoContextSwitchMarker PrimNumberUnwindMarker SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN'
- 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMForFFICall DisownVMForThreading DoAssertionChecks DoExpensiveAssertionChecks FastCPrimitiveAlignForFloatsFlag FastCPrimitiveFlag GCCheckFreeSpace GCCheckImageSegment GCCheckPrimCall GCCheckShorten GCModeBecome GCModeFull GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrFFIException PrimErrGenericFailure PrimErrInappropriate PrimErrInternalError PrimErrLimitExceeded PrimErrNamedInternal PrimErrNeedCompaction PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrOperationFailed PrimErrUninitialized PrimErrUnsupported PrimErrWritePa
 stObject PrimNoErr PrimNumberHandlerMarker PrimNumberNoContextSwitchMarker PrimNumberUnwindMarker 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.
  	PrimErrNeedCompaction	:= pet indexOf: #'heap compaction needed' ifAbsent: 23. "N.B. This is currently an internal error in Spur image segment saving."
  	PrimErrOperationFailed		:= pet indexOf: #'operation failed' ifAbsent: 24.
  	PrimErrInternalError		:= pet indexOf: #'internal error' ifAbsent: 25.
+ 	PrimErrUninitialized			:= pet indexOf: #'uninitialized' ifAbsent: 26.
+ 	PrimErrFFIMarshallingError	:= pet indexOf: #'ffi marshalling error' ifAbsent: 27!
- 	PrimErrUninitialized			:= pet indexOf: #'uninitialized' ifAbsent: 26!



More information about the Vm-dev mailing list