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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 2 15:32:56 UTC 2022


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

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

Name: VMMaker.oscog-eem.3231
Author: eem
Time: 2 August 2022, 8:32:42.653469 am
UUID: d0507db9-2a9c-40e6-9274-8e05bf0a2483
Ancestors: VMMaker.oscog-eem.3230

Fix nonRegisterStructReturnIsViaImplicitFirstArgument for ThreadedRiscV64FFIPlugin.  Make it inline always on all of them, along with a few others.

Delete the ARMv8 and RISCV versions of ffiCall:ArgArrayOrNil:NumArgs:, which were added as a misunderstanding.  Mark ffiCall:ArgArrayOrNil:NumArgs: as inline: false.  It saves about 10k, sharing the code between primitiveCallout & primitiveCalloutWithArgs.

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

Item was changed:
  ----- Method: InterpreterPlugin>>isAlien: (in category 'alien support') -----
  isAlien: oop
  	"Answer if oop is an Alien.  We could ask if isWordsOrBytes: first, but that doesn't help.  We still have to do the is:KindOf: walk.
  	 We're not interested in fast falsehood, but as fast as possible truth, and with the current API this is it."
+ 	<inline: #always>
- 	<inline: true>
  	^interpreterProxy is: oop KindOfClass: interpreterProxy classAlien!

Item was removed:
- ----- Method: ThreadedARM64FFIPlugin>>ffiCall:ArgArrayOrNil:NumArgs: (in category 'callout support') -----
- ffiCall: externalFunction ArgArrayOrNil: argArrayOrNil NumArgs: nArgs
- 	"Generic callout. Does the actual work.  If argArrayOrNil is nil it takes args from the stack
- 	 and the spec from the method.  If argArrayOrNil is not nil takes args from argArrayOrNil
- 	 and the spec from the receiver."
- 	| flags argTypeArray address argType oop argSpec argClass err theCalloutState calloutState requiredStackSize stackSize allocation result primNumArgs |
- 	<inline: false>
- 	<var: #theCalloutState type: #'CalloutState'>
- 	<var: #calloutState type: #'CalloutState *'>
- 	<var: #allocation type: #'char *'>
- 
- 	primNumArgs := interpreterProxy methodArgumentCount.
- 	(interpreterProxy is: externalFunction KindOfClass: interpreterProxy classExternalFunction) ifFalse:
- 		[^self ffiFail: FFIErrorNotFunction].
- 	"Load and check the values in the externalFunction before we call out"
- 	flags := interpreterProxy fetchInteger: ExternalFunctionFlagsIndex ofObject: externalFunction.
- 	interpreterProxy failed ifTrue:
- 		[^self ffiFail: FFIErrorBadArgs].
- 
- 	"This must come early for compatibility with the old FFIPlugin.  Image-level code
- 	 may assume the function pointer is loaded eagerly.  Thanks to Nicolas Cellier."
- 	address := self ffiLoadCalloutAddress: externalFunction.
- 	interpreterProxy failed ifTrue:
- 		[^0 "error code already set by ffiLoadCalloutAddress:"].
- 	
- 	argTypeArray := interpreterProxy fetchPointer: ExternalFunctionArgTypesIndex ofObject: externalFunction.
- 	"must be array of arg types"
- 	((interpreterProxy isArray: argTypeArray)
- 	and: [(interpreterProxy slotSizeOf: argTypeArray) = (nArgs + 1)]) ifFalse:
- 		[^self ffiFail: FFIErrorBadArgs].
- 	"check if the calling convention is supported"
- 	self cppIf: COGMTVM
- 		ifTrue:
- 			[(self ffiSupportsCallingConvention: (flags bitAnd: FFICallTypesMask)) ifFalse:
- 				[^self ffiFail: FFIErrorCallType]]
- 		ifFalse: "not masking causes threaded calls to fail, which is as they should if the plugin is not threaded."
- 			[(self ffiSupportsCallingConvention: flags) ifFalse:
- 				[^self ffiFail: FFIErrorCallType]].
- 		
- 	requiredStackSize := self externalFunctionHasStackSizeSlot
- 							ifTrue: [interpreterProxy
- 										fetchInteger: ExternalFunctionStackSizeIndex
- 										ofObject: externalFunction]
- 							ifFalse: [-1].
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: (argArrayOrNil isNil
- 												ifTrue: [PrimErrBadMethod]
- 												ifFalse: [PrimErrBadReceiver])].
- 	stackSize := requiredStackSize < 0 ifTrue: [DefaultMaxStackSize] ifFalse: [requiredStackSize].
- 	self cCode: [] inSmalltalk: [theCalloutState := self class calloutStateClass new].
- 	calloutState := self addressOf: theCalloutState.
- 	self cCode: [self memset: calloutState _: 0 _: (self sizeof: #CalloutState)].
- 	calloutState callFlags: flags.
- 	"Fetch return type and args"
- 	argType := interpreterProxy fetchPointer: 0 ofObject: argTypeArray.
- 	argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
- 	argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
- 	(err := self ffiCheckReturn: argSpec With: argClass in: calloutState) ~= 0 ifTrue:
- 		[^self ffiFail: err]. "cannot return"
- 	"alloca the outgoing stack frame, leaving room for marshalling args, and including space for the return struct, if any.
- 	Additional space reserved for saving register args like mandated by Win64 X64 or PPC ABI, will be managed by the call itself"
- 	allocation := self alloca: stackSize + calloutState structReturnSize + self cStackAlignment.
- 	self mustAlignStack ifTrue:
- 		[allocation := self cCoerce: (allocation asUnsignedIntegerPtr bitClear: self cStackAlignment - 1) to: #'char *'].
- 	calloutState
- 		argVector: allocation;
- 		currentArg: allocation;
- 		limit: allocation + stackSize.
- 	1 to: nArgs do:
- 		[:i|
- 		argType := interpreterProxy fetchPointer: i ofObject: argTypeArray.
- 		argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
- 		argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
- 		oop := argArrayOrNil isNil
- 				ifTrue: [interpreterProxy stackValue: nArgs - i]
- 				ifFalse: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
- 		err := self ffiArgument: oop Spec: argSpec Class: argClass in: calloutState.
- 		err ~= 0 ifTrue:
- 			[self cleanupCalloutState: calloutState.
- 			 self cppIf: COGMTVM ifTrue:
- 			 [err = PrimErrObjectMayMove negated ifTrue:
- 				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
- 			 ^self ffiFail: err]]. "coercion failed or out of stack space"
- 	"Failures must be reported back from ffiArgument:Spec:Class:in:.
- 	 Should not fail from here on in."
- 	self assert: interpreterProxy failed not.
- 	self ffiLogCallout: externalFunction.
- 	(requiredStackSize < 0
- 	 and: [self externalFunctionHasStackSizeSlot]) ifTrue:
- 		[stackSize := calloutState currentArg - calloutState argVector.
- 		 interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction withValue: stackSize].
- 	"Go out and call this guy"
- 	result := self ffiCalloutTo: address SpecOnStack: argArrayOrNil notNil in: calloutState.
- 	self cleanupCalloutState: calloutState.
- 	"Can not safely use argumentCount (via e.g. methodReturnValue:) since it may have been changed by a callback."
- 	interpreterProxy pop: primNumArgs + 1 thenPush: result. 
- 	^result!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>nonRegisterStructReturnIsViaImplicitFirstArgument (in category 'marshalling') -----
  nonRegisterStructReturnIsViaImplicitFirstArgument
  	"Answer if a struct returned in memory is returned to the
+ 	 referent of a pointer passed as an implicit first argument.
+ 	 It almost always is, but isn't in ARMv8 and RISCV 64 ABIs."
+ 	<inline: #always>
- 	 referent of a pointer passed as an implciit first argument.
- 	 It almost always is.  Subclasses can override if not."
  	^false!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForX64>>incrementFloatRegisterIndex (in category 'accessing') -----
  incrementFloatRegisterIndex
+ 	<inline: #always>
  	^floatRegisterIndex := floatRegisterIndex + 1!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForX64>>incrementIntegerRegisterIndex (in category 'accessing') -----
  incrementIntegerRegisterIndex
+ 	<inline: #always>
  	^integerRegisterIndex := integerRegisterIndex + 1!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForX64Win64>>incrementFloatRegisterIndex (in category 'accessing') -----
  incrementFloatRegisterIndex
  	"There are only 4 args passed by register int or float.
  	So we can't distinguish the float index from the integer index.
  	So we have to increment both.
  	
  	Consequently, floatRegisterIndex cannot be used anymore to detect presence of float parameter.
  	However, we set a signature bitmap indicating which register position is used to pass a float.
  	
  	IMPLEMENTATION NOTES:
  	There are code generator hacks that bypass the accessors.
  	So we cannot just redefine the method floatRegisterIndex as ^integerRegisterIndex.
  	Instead we must maintain the two indices"
+ 	<inline: #always>
  
  	floatRegisterSignature := floatRegisterSignature + (1 << floatRegisterIndex).
  	^integerRegisterIndex := floatRegisterIndex := floatRegisterIndex + 1!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForX64Win64>>incrementIntegerRegisterIndex (in category 'accessing') -----
  incrementIntegerRegisterIndex
  	"There are only 4 args passed by register int or float.
  	So we can't distinguish the float index from the integer index.
  	So we have to increment both.
  	
  	IMPLEMENTATION NOTES:
  	There are code generator hacks that bypass the accessors.
  	So we cannot just redefine the method floatRegisterIndex as ^integerRegisterIndex.
  	Instead we must maintain the two indices"
+ 	<inline: #always>
  
  	^floatRegisterIndex := integerRegisterIndex := integerRegisterIndex + 1!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCall:ArgArrayOrNil:NumArgs: (in category 'callout support') -----
  ffiCall: externalFunction ArgArrayOrNil: argArrayOrNil NumArgs: nArgs
  	"Generic callout. Does the actual work.  If argArrayOrNil is nil it takes args from the stack
  	 and the spec from the method.  If argArrayOrNil is not nil takes args from argArrayOrNil
  	 and the spec from the receiver."
  	| flags argTypeArray address argType oop argSpec argClass err theCalloutState calloutState requiredStackSize stackSize allocation result primNumArgs |
+ 	<inline: false>
- 	<inline: true>
  	<var: #theCalloutState type: #'CalloutState'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #allocation type: #'char *'>
  
  	primNumArgs := interpreterProxy methodArgumentCount.
  	(interpreterProxy is: externalFunction KindOfClass: interpreterProxy classExternalFunction) ifFalse:
  		[^self ffiFail: FFIErrorNotFunction].
  	"Load and check the values in the externalFunction before we call out"
  	flags := interpreterProxy fetchInteger: ExternalFunctionFlagsIndex ofObject: externalFunction.
  	interpreterProxy failed ifTrue:
  		[^self ffiFail: FFIErrorBadArgs].
  
  	"This must come early for compatibility with the old FFIPlugin.  Image-level code
  	 may assume the function pointer is loaded eagerly.  Thanks to Nicolas Cellier."
  	address := self ffiLoadCalloutAddress: externalFunction.
  	interpreterProxy failed ifTrue:
  		[^0 "error code already set by ffiLoadCalloutAddress:"].
  	
  	argTypeArray := interpreterProxy fetchPointer: ExternalFunctionArgTypesIndex ofObject: externalFunction.
  	"must be array of arg types"
  	((interpreterProxy isArray: argTypeArray)
  	and: [(interpreterProxy slotSizeOf: argTypeArray) = (nArgs + 1)]) ifFalse:
  		[^self ffiFail: FFIErrorBadArgs].
  	"check if the calling convention is supported"
  	self cppIf: COGMTVM
  		ifTrue:
  			[(self ffiSupportsCallingConvention: (flags bitAnd: FFICallTypesMask)) ifFalse:
  				[^self ffiFail: FFIErrorCallType]]
  		ifFalse: "not masking causes threaded calls to fail, which is as they should if the plugin is not threaded."
  			[(self ffiSupportsCallingConvention: flags) ifFalse:
  				[^self ffiFail: FFIErrorCallType]].
  		
  	requiredStackSize := self externalFunctionHasStackSizeSlot
  							ifTrue: [interpreterProxy
  										fetchInteger: ExternalFunctionStackSizeIndex
  										ofObject: externalFunction]
  							ifFalse: [-1].
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: (argArrayOrNil isNil
  												ifTrue: [PrimErrBadMethod]
  												ifFalse: [PrimErrBadReceiver])].
  	stackSize := requiredStackSize < 0 ifTrue: [DefaultMaxStackSize] ifFalse: [requiredStackSize].
  	self cCode: [] inSmalltalk: [theCalloutState := self class calloutStateClass new].
  	calloutState := self addressOf: theCalloutState.
  	self cCode: [self memset: calloutState _: 0 _: (self sizeof: #CalloutState)].
  	calloutState callFlags: flags.
  	"Fetch return type and args"
  	argType := interpreterProxy fetchPointer: 0 ofObject: argTypeArray.
  	argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
  	argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
  	(err := self ffiCheckReturn: argSpec With: argClass in: calloutState) ~= 0 ifTrue:
  		[^self ffiFail: err]. "cannot return"
  	"alloca the outgoing stack frame, leaving room for marshalling args, and including space for the return struct, if any.
  	Additional space reserved for saving register args like mandated by Win64 X64 or PPC ABI, will be managed by the call itself"
  	allocation := self alloca: stackSize + calloutState structReturnSize + self cStackAlignment.
  	self mustAlignStack ifTrue:
  		[allocation := self cCoerce: (allocation asUnsignedIntegerPtr bitClear: self cStackAlignment - 1) to: #'char *'].
  	calloutState
  		argVector: allocation;
  		currentArg: allocation;
  		limit: allocation + stackSize.
+ 	(self nonRegisterStructReturnIsViaImplicitFirstArgument
+ 	 and: [calloutState structReturnSize > 0
- 	(calloutState structReturnSize > 0
- 	 and: [self nonRegisterStructReturnIsViaImplicitFirstArgument
  	 and: [(self returnStructInRegisters: calloutState) not]]) ifTrue:
  		[err := self ffiPushPointer: calloutState limit in: calloutState.
  		 err ~= 0 ifTrue:
  			[self cleanupCalloutState: calloutState.
  			 self cppIf: COGMTVM ifTrue:
  			 [err = PrimErrObjectMayMove negated ifTrue:
  				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
  			 ^self ffiFail: err]].
  	1 to: nArgs do:
  		[:i|
  		argType := interpreterProxy fetchPointer: i ofObject: argTypeArray.
  		argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
  		argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
  		oop := argArrayOrNil isNil
  				ifTrue: [interpreterProxy stackValue: nArgs - i]
  				ifFalse: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
  		err := self ffiArgument: oop Spec: argSpec Class: argClass in: calloutState.
  		err ~= 0 ifTrue:
  			[self cleanupCalloutState: calloutState.
  			 self cppIf: COGMTVM ifTrue:
  			 [err = PrimErrObjectMayMove negated ifTrue:
  				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
  			 ^self ffiFail: err]]. "coercion failed or out of stack space"
  	"Failures must be reported back from ffiArgument:Spec:Class:in:.
  	 Should not fail from here on in."
  	self assert: interpreterProxy failed not.
  	self ffiLogCallout: externalFunction.
  	(requiredStackSize < 0
  	 and: [self externalFunctionHasStackSizeSlot]) ifTrue:
  		[stackSize := calloutState currentArg - calloutState argVector.
  		 interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction withValue: stackSize].
  	"Go out and call this guy"
  	result := self ffiCalloutTo: address SpecOnStack: argArrayOrNil notNil in: calloutState.
  	self cleanupCalloutState: calloutState.
  	"Can not safely use argumentCount (via e.g. methodReturnValue:) since it may have been changed by a callback."
  	interpreterProxy pop: primNumArgs + 1 thenPush: result. 
  	^result!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiSupportsCallingConvention: (in category 'callout support') -----
  ffiSupportsCallingConvention: aCallingConvention
  	"Check that the calling convention is valid.  This test also filters out attempts
  	 to do a threaded call in the non-threaded VM/plugin combinatioin."
  
+ 	<inline: #always>
- 	<inline: true>
  	^aCallingConvention = FFICallTypeCDecl or: [aCallingConvention = FFICallTypeApi]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>isDirectAlien: (in category 'primitive support') -----
  isDirectAlien: oop
+ 	<inline: #always>
  	self assert: (self isAlien: oop).
  	^(self sizeField: oop) > 0!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>isFloatAtomicType: (in category 'primitive support') -----
  isFloatAtomicType: atomicTypeCode
+ 	<inline: #always>
- 	<inline: true>
  	"(atomicTypeCode >> 1) = (FFITypeSingleFloat >> 1)"
  	^atomicTypeCode >> 1 = 6 !

Item was changed:
  ----- Method: ThreadedFFIPlugin>>nonRegisterStructReturnIsViaImplicitFirstArgument (in category 'marshalling-struct') -----
  nonRegisterStructReturnIsViaImplicitFirstArgument
  	"Answer if a struct returned in memory is returned to the
+ 	 referent of a pointer passed as an implicit first argument.
- 	 referent of a pointer passed as an implciit first argument.
  	 It almost always is.  Subclasses can override if not."
+ 	<inline: #always>
  	^true!

Item was removed:
- ----- Method: ThreadedRiscV64FFIPlugin>>ffiCall:ArgArrayOrNil:NumArgs: (in category 'callout support') -----
- ffiCall: externalFunction ArgArrayOrNil: argArrayOrNil NumArgs: nArgs
- 	"Generic callout. Does the actual work.  If argArrayOrNil is nil it takes args from the stack
- 	 and the spec from the method.  If argArrayOrNil is not nil takes args from argArrayOrNil
- 	 and the spec from the receiver."
- 	| flags argTypeArray address argType oop argSpec argClass err theCalloutState calloutState requiredStackSize stackSize allocation result primNumArgs |
- 	<inline: false>
- 	<var: #theCalloutState type: #'CalloutState'>
- 	<var: #calloutState type: #'CalloutState *'>
- 	<var: #allocation type: #'char *'>
- 
- 	primNumArgs := interpreterProxy methodArgumentCount.
- 	(interpreterProxy is: externalFunction KindOfClass: interpreterProxy classExternalFunction) ifFalse:
- 		[^self ffiFail: FFIErrorNotFunction].
- 	"Load and check the values in the externalFunction before we call out"
- 	flags := interpreterProxy fetchInteger: ExternalFunctionFlagsIndex ofObject: externalFunction.
- 	interpreterProxy failed ifTrue:
- 		[^self ffiFail: FFIErrorBadArgs].
- 
- 	"This must come early for compatibility with the old FFIPlugin.  Image-level code
- 	 may assume the function pointer is loaded eagerly.  Thanks to Nicolas Cellier."
- 	address := self ffiLoadCalloutAddress: externalFunction.
- 	interpreterProxy failed ifTrue:
- 		[^0 "error code already set by ffiLoadCalloutAddress:"].
- 	
- 	argTypeArray := interpreterProxy fetchPointer: ExternalFunctionArgTypesIndex ofObject: externalFunction.
- 	"must be array of arg types"
- 	((interpreterProxy isArray: argTypeArray)
- 	and: [(interpreterProxy slotSizeOf: argTypeArray) = (nArgs + 1)]) ifFalse:
- 		[^self ffiFail: FFIErrorBadArgs].
- 	"check if the calling convention is supported"
- 	self cppIf: COGMTVM
- 		ifTrue:
- 			[(self ffiSupportsCallingConvention: (flags bitAnd: FFICallTypesMask)) ifFalse:
- 				[^self ffiFail: FFIErrorCallType]]
- 		ifFalse: "not masking causes threaded calls to fail, which is as they should if the plugin is not threaded."
- 			[(self ffiSupportsCallingConvention: flags) ifFalse:
- 				[^self ffiFail: FFIErrorCallType]].
- 		
- 	requiredStackSize := self externalFunctionHasStackSizeSlot
- 							ifTrue: [interpreterProxy
- 										fetchInteger: ExternalFunctionStackSizeIndex
- 										ofObject: externalFunction]
- 							ifFalse: [-1].
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: (argArrayOrNil isNil
- 												ifTrue: [PrimErrBadMethod]
- 												ifFalse: [PrimErrBadReceiver])].
- 	stackSize := requiredStackSize < 0 ifTrue: [DefaultMaxStackSize] ifFalse: [requiredStackSize].
- 	self cCode: [] inSmalltalk: [theCalloutState := self class calloutStateClass new].
- 	calloutState := self addressOf: theCalloutState.
- 	self cCode: [self memset: calloutState _: 0 _: (self sizeof: #CalloutState)].
- 	calloutState callFlags: flags.
- 	"Fetch return type and args"
- 	argType := interpreterProxy fetchPointer: 0 ofObject: argTypeArray.
- 	argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
- 	argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
- 	(err := self ffiCheckReturn: argSpec With: argClass in: calloutState) ~= 0 ifTrue:
- 		[^self ffiFail: err]. "cannot return"
- 	"alloca the outgoing stack frame, leaving room for marshalling args, and including space for the return struct, if any.
- 	Additional space reserved for saving register args like mandated by Win64 X64 or PPC ABI, will be managed by the call itself"
- 	allocation := self alloca: stackSize + calloutState structReturnSize + self cStackAlignment.
- 	self mustAlignStack ifTrue:
- 		[allocation := self cCoerce: (allocation asUnsignedIntegerPtr bitClear: self cStackAlignment - 1) to: #'char *'].
- 	calloutState
- 		argVector: allocation;
- 		currentArg: allocation;
- 		limit: allocation + stackSize.
- 	"This next bit overrides the ARM64 code to pass return struct pointer in A0"
- 	(calloutState structReturnSize > 0
- 	 and: [self nonRegisterStructReturnIsViaImplicitFirstArgument
- 	 and: [(self returnStructInRegisters: calloutState) not]]) ifTrue:
- 		[err := self ffiPushPointer: calloutState limit in: calloutState.
- 		 err ~= 0 ifTrue:
- 			[self cleanupCalloutState: calloutState.
- 			 self cppIf: COGMTVM ifTrue:
- 			 [err = PrimErrObjectMayMove negated ifTrue:
- 				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
- 			 ^self ffiFail: err]].
- 	"Aside from the bit above, code identical with arm64"
- 	1 to: nArgs do:
- 		[:i|
- 		argType := interpreterProxy fetchPointer: i ofObject: argTypeArray.
- 		argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
- 		argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
- 		oop := argArrayOrNil isNil
- 				ifTrue: [interpreterProxy stackValue: nArgs - i]
- 				ifFalse: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
- 		err := self ffiArgument: oop Spec: argSpec Class: argClass in: calloutState.
- 		err ~= 0 ifTrue:
- 			[self cleanupCalloutState: calloutState.
- 			 self cppIf: COGMTVM ifTrue:
- 			 [err = PrimErrObjectMayMove negated ifTrue:
- 				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
- 			 ^self ffiFail: err]]. "coercion failed or out of stack space"
- 	"Failures must be reported back from ffiArgument:Spec:Class:in:.
- 	 Should not fail from here on in."
- 	self assert: interpreterProxy failed not.
- 	self ffiLogCallout: externalFunction.
- 	(requiredStackSize < 0
- 	 and: [self externalFunctionHasStackSizeSlot]) ifTrue:
- 		[stackSize := calloutState currentArg - calloutState argVector.
- 		 interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction withValue: stackSize].
- 	"Go out and call this guy"
- 	result := self ffiCalloutTo: address SpecOnStack: argArrayOrNil notNil in: calloutState.
- 	self cleanupCalloutState: calloutState.
- 	"Can not safely use argumentCount (via e.g. methodReturnValue:) since it may have been changed by a callback."
- 	interpreterProxy pop: primNumArgs + 1 thenPush: result. 
- 	^result!

Item was removed:
- ----- Method: ThreadedRiscV64FFIPlugin>>nonRegisterStructReturnIsViaImplicitFirstArgument (in category 'marshalling') -----
- nonRegisterStructReturnIsViaImplicitFirstArgument
- 	"Answer if a struct returned in memory is returned to the
- 	 referent of a pointer passed as an implciit first argument.
- 	 It almost always is.  Subclasses can override if not."
- 	^true!



More information about the Vm-dev mailing list