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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 16 02:18:13 UTC 2022


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

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

Name: VMMaker.oscog-eem.3156
Author: eem
Time: 15 February 2022, 6:12:25.887338 pm
UUID: 1000a975-b96e-40bb-8c41-47dbd0a06e3e
Ancestors: VMMaker.oscog-eem.3155

ThreadedFFI ARM64 plugin:
Apple diverges significantly from the standard.  In particular, stacked arguments are packed like a struct (char takes one byte, short is aligned on a doublebyte boundary and takes two bytes, etc). Hence introduce ThreadedARM64AppleFFIPlugin as a subclass of ThreadedARM64FFIPlugin.

Have ThreadedARM64FFIPlugin inherit from ThreadedFFIPlugin; it inherits nothing from ThreadedARM32FFIPlugin. Rename the ThreadedFFIX64SixteenByteReturnXX classes since they are more generally useful.  In particular use ThreadedFFI64Bit16ByteReturnII to implement struct (and integer) return on ARM64.  Hence get rid of getX1register (& returnX1value).

Fix two typos in primitiveSignedInt32At et al.

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

Item was added:
+ ThreadedARM64FFIPlugin subclass: #ThreadedARM64AppleFFIPlugin
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!
+ 
+ !ThreadedARM64AppleFFIPlugin commentStamp: 'eem 2/15/2022 14:12' prior: 0!
+ A ThreadedARM64AppleFFIPlugin is a version of ThreadedARM64FFIPlugin that implements Apple's divergences from the ARM64 standard ABI, as described on https://developer.apple.com/documentation/xcode/writing-arm64-code-for-apple-platforms in section "Pass Arguments to Functions Correctly".
+ 
+ Instance Variables
+ !

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin class>>excludingPredefinedMacros (in category 'translation') -----
+ excludingPredefinedMacros
+ 	^nil!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin class>>moduleName (in category 'translation') -----
+ moduleName
+ 	^'ARM64AppleFFIPlugin'!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>alignCurrentArgOf:to: (in category 'marshalling') -----
+ alignCurrentArgOf: calloutState to: boundary
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	| misAlignedBytes |
+ 	misAlignedBytes := calloutState currentArg asInteger bitAnd: boundary - 1.
+ 	misAlignedBytes ~= 0 ifTrue:
+ 		[calloutState currentArg: calloutState currentArg + (boundary - misAlignedBytes)]!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushFloat32:in: (in category 'marshalling') -----
+ ffiPushFloat32: value in: calloutState
+ 	<var: #value type: #float>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState floatRegisterIndex < NumFloatRegArgs
+ 		ifTrue: "Note: this is a 'memcopy', so size is preserved. Casting to #double changes the size"
+ 			[(self cCoerceSimple: 
+ 				(self addressOf: (calloutState floatRegisters at: calloutState floatRegisterIndex)) 
+ 					 to: 'float*')
+ 				at: 0
+ 				put: value.
+ 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 4.
+ 			 interpreterProxy storeSingleFloatAtPointer: calloutState currentArg from: value.
+ 			 calloutState currentArg: calloutState currentArg + 4].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushFloat64:in: (in category 'marshalling') -----
+ ffiPushFloat64: value in: calloutState
+ 	<var: #value type: #double>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 
+ 	calloutState floatRegisterIndex < NumFloatRegArgs
+ 		ifTrue:
+ 			[calloutState floatRegisters
+ 				at: calloutState floatRegisterIndex
+ 				put: value.
+ 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 calloutState floatRegisterIndex: NumFloatRegArgs.
+ 			 self alignCurrentArgOf: calloutState to: 8.
+ 			 interpreterProxy storeFloatAtPointer: calloutState currentArg from: value.
+ 			 calloutState currentArg: calloutState currentArg + 8].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
+ ffiPushPointer: pointer in: calloutState
+ 	<var: #pointer type: #'void *'>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: pointer asInteger.
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: self wordSize.
+ 			 interpreterProxy longAt: calloutState currentArg put: pointer.
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushSigned16:in: (in category 'marshalling') -----
+ ffiPushSigned16: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'signed short').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 2.
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed short').
+ 			 calloutState currentArg: calloutState currentArg + 2].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushSigned32:in: (in category 'marshalling') -----
+ ffiPushSigned32: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters 
+ 				at: calloutState integerRegisterIndex 
+ 				put: (self cCoerceSimple: value to: #sqLong).
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 4.
+ 			 interpreterProxy longAt: calloutState currentArg put: value.
+ 			 calloutState currentArg: calloutState currentArg + 4].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushSigned64:in: (in category 'marshalling') -----
+ ffiPushSigned64: value in: calloutState
+ 	<var: #value type: #sqLong>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters 
+ 				at: calloutState integerRegisterIndex 
+ 				put: (self cCoerceSimple: value to: #sqLong).
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 8.
+ 			 interpreterProxy longAt: calloutState currentArg put: value.
+ 			 calloutState currentArg: calloutState currentArg + 8].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushSigned8:in: (in category 'marshalling') -----
+ ffiPushSigned8: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'signed char').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed char').
+ 			 calloutState currentArg: calloutState currentArg + 1].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushStructure:ofSize:typeSpec:ofLength:in: (in category 'marshalling') -----
+ ffiPushStructure: pointer ofSize: structSize typeSpec: argSpec ofLength: argSpecSize in: calloutState
+ 	<var: #pointer type: #'void *'>
+ 	<var: #argSpec type: #'unsigned int *'>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	| availableRegisterSpace stackPartSize roundedSize |
+ 	"See IHI0055B_aapcs64.pdf sections 4.3.5 & 5.4.2 Stage C; we don't yet support HVA's"
+ 	(self structIsHomogenousFloatArrayOfSize: structSize typeSpec: argSpec ofLength: argSpecSize)
+ 		ifTrue:
+ 			[availableRegisterSpace := (NumFloatRegArgs - calloutState floatRegisterIndex) * self wordSize.
+ 			 structSize <= availableRegisterSpace ifTrue: "Stage C, step C.2, all in floating-point registers (!!!!)"
+ 				[self 
+ 					memcpy: (self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: calloutState floatRegisterIndex)) to: #'void *') 
+ 					_: pointer 
+ 					_: structSize.
+ 					"Round structSize up and divide by 8 ( NB: _not_ 4 !!)"
+ 				 calloutState floatRegisterIndex: calloutState floatRegisterIndex + (structSize + 7 bitShift: -3).
+ 				 ^0].
+ 			 "Stage C, step C.3"
+ 			 availableRegisterSpace := 0.
+ 			 calloutState floatRegisterIndex: 8]
+ 
+ 		ifFalse:
+ 			[availableRegisterSpace := (NumIntRegArgs - calloutState integerRegisterIndex) * self wordSize].
+ 	stackPartSize := structSize.
+ 	availableRegisterSpace > 0 ifTrue: 
+ 		[structSize <= availableRegisterSpace ifTrue:"all in integer registers"
+ 			[self 
+ 				memcpy: (self cCoerceSimple: (self addressOf: (calloutState integerRegisters at: calloutState integerRegisterIndex)) to: #'void *') 
+ 				_: pointer 
+ 				_: structSize.
+ 				"Round structSize up and divide by 8 ( NB: _not_ 4 !!)"
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + (structSize + 7 bitShift: -3).
+ 			 ^0].
+ 		 "If no previous co-processor candidate arg has already been pushed on the stack, then split the struct between registers and stack.
+ 		  Otherwise push entire struct on stack."
+ 		 calloutState currentArg = calloutState argVector
+ 			ifTrue: 
+ 		 		[stackPartSize := structSize - availableRegisterSpace.
+ 		 		self 
+ 					memcpy: (self cCoerceSimple: (self addressOf: (calloutState integerRegisters at: calloutState integerRegisterIndex)) to: 'void *') 
+ 					_: pointer 
+ 					_: availableRegisterSpace]
+ 			ifFalse:
+ 				[availableRegisterSpace := 0].
+ 		"Stage C, step C.11"
+ 		calloutState integerRegisterIndex: NumIntRegArgs].
+ 
+ 	stackPartSize > 0 ifTrue: 
+ 		[roundedSize := stackPartSize + 3 bitClear: 3.
+ 		 calloutState currentArg + roundedSize > calloutState limit ifTrue:
+ 			 [^FFIErrorCallFrameTooBig].
+ 		 self alignCurrentArgOf: calloutState to: 8.
+ 		 self memcpy: calloutState currentArg _: (self addressOf: ((self cCoerceSimple: pointer to: #'char *') at: availableRegisterSpace)) _: stackPartSize.
+ 		 calloutState currentArg: calloutState currentArg + roundedSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushUnsigned16:in: (in category 'marshalling') -----
+ ffiPushUnsigned16: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned short').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 2.
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned short').
+ 			 calloutState currentArg: calloutState currentArg + 2].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushUnsigned32:in: (in category 'marshalling') -----
+ ffiPushUnsigned32: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: value.
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 4.
+ 			 interpreterProxy longAt: calloutState currentArg put: value.
+ 			 calloutState currentArg: calloutState currentArg + 4].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushUnsigned64:in: (in category 'marshalling') -----
+ ffiPushUnsigned64: value in: calloutState
+ 	<var: #value type: #usqLong>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters 
+ 				at: calloutState integerRegisterIndex 
+ 				put:(self cCoerceSimple: value to: #usqLong).
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
+ 			 self alignCurrentArgOf: calloutState to: 8.
+ 			 interpreterProxy longAt: calloutState currentArg put: value.
+ 			 calloutState currentArg: calloutState currentArg + 8].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64AppleFFIPlugin>>ffiPushUnsigned8:in: (in category 'marshalling') -----
+ ffiPushUnsigned8: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned char').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned char').
+ 			 calloutState currentArg: calloutState currentArg + 1].
+ 	^0!

Item was changed:
+ ThreadedFFIPlugin subclass: #ThreadedARM64FFIPlugin
- ThreadedARM32FFIPlugin subclass: #ThreadedARM64FFIPlugin
  	instanceVariableNames: ''
+ 	classVariableNames: 'NumFloatRegArgs NumIntRegArgs'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Plugins-FFI'!
  
+ !ThreadedARM64FFIPlugin commentStamp: 'KenD 12/17/2018 14:38' prior: 0!
- !ThreadedARM64FFIPlugin commentStamp: '' prior: 0!
  A ThreadedARM64FFIPlugin is for the 64-bit ARM ABI.  It typically has 8 integer registers
  
  Instance Variables
  !

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	^super ancilliaryClasses,
+ 	  { ThreadedFFI64Bit16ByteReturnII }!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin class>>excludingPredefinedMacros (in category 'translation') -----
+ excludingPredefinedMacros
+ 	^#('__APPLE__')!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double, double, double, double, double)'>
  	"Go out, call this guy and create the return value.  This *must* be inlined because of
  	 the alloca of the outgoing stack frame in ffiCall:WithFlags:NumArgs:Args:AndTypes:"
+ 	| myThreadIndex atomicType floatRet intRet structRet specSize |
- 	| myThreadIndex atomicType floatRet intRet x1Ret specSize |
  	<var: #floatRet type: 'union { struct { float floats[8]; } f; struct dprr { double doubles[4]; } d; }'>
+ 	<var: #structRet type: #SixteenByteReturnII>
  	<var: #intRet type: #usqLong>
- 	<var: #x1Ret type: #usqLong>
  	<inline: #always>
+ 	self cCode: [] inSmalltalk: [floatRet := ByteArray new: 32]. "Just a hack to placate the Smalltalk compiler; these should be proper struct types..."
- 	self cCode: [] inSmalltalk: [floatRet := ByteArray new: 32]. "Just a hack to placate the Smalltalk compiler; this shoudl be a proper struct..."
  	myThreadIndex := interpreterProxy disownVM: (self disownFlagsFor: calloutState).
  	
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self loadFloatRegs:
  			   (calloutState floatRegisters at: 0)
  			_: (calloutState floatRegisters at: 1)
  			_: (calloutState floatRegisters at: 2)
  			_: (calloutState floatRegisters at: 3)
  			_: (calloutState floatRegisters at: 4)
  			_: (calloutState floatRegisters at: 5)
  			_: (calloutState floatRegisters at: 6)
  			_: (calloutState floatRegisters at: 7)].
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	((atomicType >> 1) = (FFITypeSingleFloat >> 1)
  	or: [(calloutState ffiRetHeader bitAnd: FFIFlagPointer+FFIFlagStructure) = FFIFlagStructure
  		and: [self structIsHomogenousFloatArrayOfSize: (calloutState ffiRetHeader bitAnd: FFIStructSizeMask)
  				typeSpec: (self cCoerce: (interpreterProxy firstIndexableField: calloutState ffiRetSpec) to: #'unsigned int *')
  				ofLength: (specSize := interpreterProxy byteSizeOf: calloutState ffiRetSpec) / (self sizeof: #'unsigned int')]]) ifTrue:
  		[floatRet d: (self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'struct dprr (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')
  					with: (calloutState integerRegisters at: 0)
  					with: (calloutState integerRegisters at: 1)
  					with: (calloutState integerRegisters at: 2)
  					with: (calloutState integerRegisters at: 3)
  					with: (calloutState integerRegisters at: 4)
  					with: (calloutState integerRegisters at: 5)
  					with: (calloutState integerRegisters at: 6)
  					with: (calloutState integerRegisters at: 7)).
  
  		 "undo any callee argument pops because it may confuse stack management with the alloca."
  		 (self isCalleePopsConvention: calloutState callFlags) ifTrue:
  			[self setsp: calloutState argVector].
  		 interpreterProxy ownVM: myThreadIndex.
  
  		 atomicType = FFITypeDoubleFloat ifTrue:
  			[^interpreterProxy floatObjectOf: (floatRet d doubles at: 0)].
  		 atomicType = FFITypeSingleFloat ifTrue:
  			[^interpreterProxy floatObjectOf: (floatRet f floats at: 0)].
  		"If the struct is a vector of floats then move float[2] to float[1], float[4] to float[2] and float[6] to float[3],
  		 to pack the float data in the double fields.  We can tell if the struct is composed of floats if its size is less
  		 than the spec size, since the spec size is (1 + n fields) * 4 bytes, and the struct size is n fields * 4 bytes
  		 for floats and n fields * 8 bytes for doubles.  We can't access the spec post call because it may have moved."
  		specSize > calloutState structReturnSize ifTrue:
  			[floatRet f floats at: 1 put: (floatRet f floats at: 2).
  			 floatRet f floats at: 2 put: (floatRet f floats at: 4).
  			 floatRet f floats at: 3 put: (floatRet f floats at: 6)].
  		^self ffiReturnStruct: (self addressOf: floatRet) ofType: (self ffiReturnType: specOnStack) in: calloutState].
  
+ 	"Integer and Structure returns..."
+ 	"If struct address used for return value, call is special; struct return pointer must be in x8"
- 	"If struct address used for return value, call is special"
  	(self mustReturnStructOnStack: calloutState structReturnSize) 
+ 		ifTrue:
+ 			[intRet := 0.
+ 			self setReturnRegister: (self cCoerceSimple: calloutState limit to: #sqLong) "stack alloca'd struct"
+ 				 andCall: (self cCoerceSimple: procAddr to: #sqLong)
+ 				 withArgsArray: (self cCoerceSimple: (self addressOf: calloutState integerRegisters) to: #sqLong)]
+ 		ifFalse:
+ 			[structRet := self 
+ 					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnII (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')
+ 					with: (calloutState integerRegisters at: 0)
+ 					with: (calloutState integerRegisters at: 1)
+ 					with: (calloutState integerRegisters at: 2)
+ 					with: (calloutState integerRegisters at: 3)
+ 					with: (calloutState integerRegisters at: 4)
+ 					with: (calloutState integerRegisters at: 5)
+ 					with: (calloutState integerRegisters at: 6)
+ 					with: (calloutState integerRegisters at: 7).
+ 			intRet := structRet a]. "X1"
- 	ifTrue: [
- 		intRet := 0.
- 		self setReturnRegister: (self cCoerceSimple: calloutState limit to: #sqLong) "stack alloca'd struct"
- 			 andCall: (self cCoerceSimple: procAddr to: #sqLong)
- 			 withArgsArray: (self cCoerceSimple: (self addressOf: calloutState integerRegisters) to: #sqLong).
- 	] ifFalse: [
- 		intRet := self 
- 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')
- 				with: (calloutState integerRegisters at: 0)
- 				with: (calloutState integerRegisters at: 1)
- 				with: (calloutState integerRegisters at: 2)
- 				with: (calloutState integerRegisters at: 3)
- 				with: (calloutState integerRegisters at: 4)
- 				with: (calloutState integerRegisters at: 5)
- 				with: (calloutState integerRegisters at: 6)
- 				with: (calloutState integerRegisters at: 7).
- 	
- 	 x1Ret := self getX1register. "Capture x1 immediately. No problem if unused"
- 	].
- 	"If struct returned in registers, 
- 	 place register values into calloutState integerRegisters"
- 	(calloutState structReturnSize > 0
- 	 and: [self returnStructInRegisters: calloutState]) ifTrue: 
- 		["Only 2 regs used in ARMv8/Aarch64 current"
- 		 calloutState integerRegisters at: 0 put: intRet. "X0"
- 		 calloutState integerRegisters at: 1 put: x1Ret]. "X1"
  
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  	interpreterProxy ownVM: myThreadIndex.
  
  	(calloutState ffiRetHeader anyMask: FFIFlagPointer+FFIFlagStructure) ifTrue:
  		["Note: Order is important here since FFIFlagPointer + FFIFlagStructure is used to represent
  		 'typedef void* VoidPointer' and VoidPointer must be returned as pointer *not* as struct."
  		 (calloutState ffiRetHeader anyMask: FFIFlagPointer) ifTrue:
  			[^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^self ffiReturnStruct: (((self returnStructInRegisters: calloutState)
+ 								ifTrue: [self cCoerceSimple: (self addressOf: structRet) to: #'char *']
- 								ifTrue: [self addressOf: calloutState integerRegisters]
  								ifFalse: [calloutState limit]))
  				ofType: (self ffiReturnType: specOnStack)
  				in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
+ ffiPushPointer: pointer in: calloutState
+ 	<var: #pointer type: #'void *'>
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: pointer asInteger.
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: pointer.
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin>>ffiPushSigned16:in: (in category 'marshalling') -----
+ ffiPushSigned16: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'signed short').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed short').
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin>>ffiPushSigned8:in: (in category 'marshalling') -----
+ ffiPushSigned8: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'signed char').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed char').
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin>>ffiPushUnsigned16:in: (in category 'marshalling') -----
+ ffiPushUnsigned16: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned short').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned short').
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was added:
+ ----- Method: ThreadedARM64FFIPlugin>>ffiPushUnsigned8:in: (in category 'marshalling') -----
+ ffiPushUnsigned8: value in: calloutState
+ 	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
+ 	calloutState integerRegisterIndex < NumIntRegArgs
+ 		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned char').
+ 			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
+ 		ifFalse:
+ 			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
+ 				[^FFIErrorCallFrameTooBig].
+ 			 interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned char').
+ 			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!

Item was removed:
- ----- Method: ThreadedARM64FFIPlugin>>getX1register (in category 'callout support') -----
- getX1register
- 
- 	<inline: true>
- 	<var: #returnX1value declareC: 'extern sqLong returnX1value()'>
- 
- 	^self returnX1value!

Item was added:
+ ThreadedFFIAbstractStructReturnStruct subclass: #ThreadedFFI64Bit16ByteReturnDD
+ 	instanceVariableNames: 'a b'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!
+ 
+ !ThreadedFFI64Bit16ByteReturnDD commentStamp: 'nice 1/25/2020 17:43' prior: 0!
+ A ThreadedFFIX64SixteenByteReturnDD is a stub for returning a struct by value through 2 eight-byte float registers
+ That is (XMM0 XMM1) on X64.
+ 
+ Instance Variables
+ 	a:		<Object> 
+ 	b:		<Object> 
+ 
+ a
+ 	- stub for first eighbyte
+ 
+ b
+ 	- stub for second eighbyte
+ !

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDD class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
+ 
+ 	aBinaryBlock value: 'a' value: #double.
+ 	aBinaryBlock value: 'b' value: #double.!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDD>>a (in category 'accessing') -----
+ a
+ 
+ 	^ a!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDD>>a: (in category 'accessing') -----
+ a: anObject
+ 
+ 	^a := anObject!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDD>>b (in category 'accessing') -----
+ b
+ 
+ 	^ b!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDD>>b: (in category 'accessing') -----
+ b: anObject
+ 
+ 	^b := anObject!

Item was added:
+ ThreadedFFIAbstractStructReturnStruct subclass: #ThreadedFFI64Bit16ByteReturnDI
+ 	instanceVariableNames: 'a b'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!
+ 
+ !ThreadedFFI64Bit16ByteReturnDI commentStamp: 'nice 1/25/2020 17:44' prior: 0!
+ A ThreadedFFIX64SixteenByteReturnDI is a stub for returning a struct by value through 1 eight-byte float register and 1 eight-byte int register
+ That is (XMM0 RAX) on X64.
+ 
+ Instance Variables
+ 	a:		<Object> 
+ 	b:		<Object> 
+ 
+ a
+ 	- stub for first eighbyte
+ 
+ b
+ 	- stub for second eighbyte
+ !

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDI class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
+ 
+ 	aBinaryBlock value: 'a' value: #double.
+ 	aBinaryBlock value: 'b' value: #sqInt.!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDI>>a (in category 'accessing') -----
+ a
+ 
+ 	^ a!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDI>>a: (in category 'accessing') -----
+ a: anObject
+ 
+ 	^a := anObject!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDI>>b (in category 'accessing') -----
+ b
+ 
+ 	^ b!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnDI>>b: (in category 'accessing') -----
+ b: anObject
+ 
+ 	^b := anObject!

Item was added:
+ ThreadedFFIAbstractStructReturnStruct subclass: #ThreadedFFI64Bit16ByteReturnID
+ 	instanceVariableNames: 'a b'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!
+ 
+ !ThreadedFFI64Bit16ByteReturnID commentStamp: 'nice 1/25/2020 17:45' prior: 0!
+ A ThreadedFFIX64SixteenByteReturnID is a stub for returning a struct by value through 1 eight-byte int register and 1 eight-byte float register
+ That is (RAX XMM0) on X64.
+ 
+ Instance Variables
+ 	a:		<Object> 
+ 	b:		<Object> 
+ 
+ a
+ 	- stub for first eighbyte
+ 
+ b
+ 	- stub for second eighbyte
+ !

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnID class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
+ 
+ 	aBinaryBlock value: 'a' value: #sqInt.
+ 	aBinaryBlock value: 'b' value: #double.!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnID>>a (in category 'accessing') -----
+ a
+ 
+ 	^ a!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnID>>a: (in category 'accessing') -----
+ a: anObject
+ 
+ 	^a := anObject!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnID>>b (in category 'accessing') -----
+ b
+ 
+ 	^ b!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnID>>b: (in category 'accessing') -----
+ b: anObject
+ 
+ 	^b := anObject!

Item was added:
+ ThreadedFFIAbstractStructReturnStruct subclass: #ThreadedFFI64Bit16ByteReturnII
+ 	instanceVariableNames: 'a b'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!
+ 
+ !ThreadedFFI64Bit16ByteReturnII commentStamp: 'nice 1/25/2020 17:44' prior: 0!
+ A ThreadedFFIX64SixteenByteReturnII is a stub for returning a struct by value through 2 eight-byte int registers
+ That is (RAX RDX) on X64.
+ 
+ Instance Variables
+ 	a:		<Object> 
+ 	b:		<Object> 
+ 
+ a
+ 	- stub for first eighbyte
+ 
+ b
+ 	- stub for second eighbyte
+ !

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnII class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
+ 
+ 	aBinaryBlock value: 'a' value: #sqInt.
+ 	aBinaryBlock value: 'b' value: #sqInt.!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnII>>a (in category 'accessing') -----
+ a
+ 
+ 	^ a!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnII>>a: (in category 'accessing') -----
+ a: anObject
+ 
+ 	^a := anObject!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnII>>b (in category 'accessing') -----
+ b
+ 
+ 	^ b!

Item was added:
+ ----- Method: ThreadedFFI64Bit16ByteReturnII>>b: (in category 'accessing') -----
+ b: anObject
+ 
+ 	^b := anObject!

Item was added:
+ VMStructType subclass: #ThreadedFFIAbstractStructReturnStruct
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins-FFI'!

Item was added:
+ ----- Method: ThreadedFFIAbstractStructReturnStruct class>>structTypeName (in category 'translation') -----
+ structTypeName
+ 	^'SixteenByteReturn', (self name last: 2)!

Item was changed:
  ----- Method: ThreadedFFIPlugin class>>generateCodeStringForPrimitives (in category 'translation') -----
  generateCodeStringForPrimitives
  	"Output a skeletal SqueakFFIPrims.c that includes the relevant FooFFIPlugin.c for
  	 each subclass based on the identifyingPredefinedMacros the subclass defines."
  	 
  	^String streamContents:
  		[:s|
  		 s nextPutAll: '/* Automatically generated by\	' withCRs.
  		 s nextPutAll: (CCodeGenerator monticelloDescriptionFor: self).
  		 s cr; nextPutAll: ' */'.
  		 s cr; cr; nextPut: $#.
+ 		 (self allSubclasses sort: [:a :b| (a inheritsFrom: b)
+ 											ifTrue: [false]
+ 											ifFalse:
+ 												[(b inheritsFrom: a)
+ 												or: [a name < b name]]]) do:
- 		 (self allSubclasses sort: [:a :b| a name < b name]) do:
  			[:class |
  			class identifyingPredefinedMacros ifNotNil:
  				[:predefinedMacros|
  				 s nextPutAll: 'if '.
  				class includingPredefinedMacros ifNotNil:
  					[:includingMacros|
  					 includingMacros do:
  						[:predefinedMacro| s nextPutAll: 'defined('; nextPutAll: predefinedMacro; nextPutAll: ') && '].
  					 s nextPut: $(].
  				class excludingPredefinedMacros ifNotNil:
  					[:excludingMacros|
  					 excludingMacros do:
  						[:predefinedMacro| s nextPutAll: '!!defined('; nextPutAll: predefinedMacro; nextPutAll: ') && '].
  					 s nextPut: $(].
  				 predefinedMacros
  					do: [:predefinedMacro| s nextPutAll: 'defined('; nextPutAll: predefinedMacro; nextPut: $)]
  					separatedBy: [s nextPutAll: ' || '].
  				class excludingPredefinedMacros ifNotNil:
  					[s nextPut: $)].
  				class includingPredefinedMacros ifNotNil:
  					[s nextPut: $)].
  				 s cr; cr; nextPutAll: '# define '; nextPutAll: class moduleName; nextPutAll: '_exports ';
  												nextPutAll: self moduleName; nextPutAll: '_exports'.
  				 s cr; nextPutAll: '# include "'; nextPutAll: class moduleName; nextPutAll: '.c"'.
  				 s cr; cr; nextPutAll: '#el']].
  		 s nextPutAll: 'se'.
  		 #(	'As yet no FFI implementation appears to exist for your platform.'
  			'Consider implementing it, starting by adding a subclass of ThreadedFFIPlugin.') do:
  			[:msg| s cr; nextPutAll: '# error '; nextPutAll: msg].
  		 s cr; nextPutAll: '#endif'; cr]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveSignedInt32At (in category 'primitives') -----
  primitiveSignedInt32At
+ 	"Answer the signed 32-bit integer starting at the given byte offset (native endian)."
- 	"Answer the signed 16-bit integer starting at the given byte offset (native endian)."
  	<export: true>
  	<primitiveMetadata: #FastCPrimitiveFlag>
  	| byteOffset rcvr |
  
  	byteOffset := interpreterProxy stackValue: 0.
  	rcvr := interpreterProxy stackValue: 1.
  	(interpreterProxy isIntegerObject: byteOffset) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self ffiAddressOf: rcvr startingAt: (interpreterProxy integerValueOf: byteOffset) size: (self sizeof: #int))
  		ifNil: [^interpreterProxy primitiveFailFor: PrimErrBadIndex]
  		ifNotNil:
  			[:addr|
  			^interpreterProxy methodReturnValue:
  				(interpreterProxy signed32BitIntegerFor: (self cCoerce: (interpreterProxy unalignedLong32At: addr) to: #'signed int'))]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveUnsignedInt16AtPut (in category 'primitives') -----
  primitiveUnsignedInt16AtPut
+ 	"Store the unsigned 16-bit integer starting at the given byte offset (native endian)."
- 	"Store the signed 16-bit integer starting at the given byte offset (native endian)."
  	<export: true>
  	<primitiveMetadata: #FastCPrimitiveFlag>
  	| valueArg value byteOffset rcvr |
  	valueArg := interpreterProxy stackValue: 0.
  	byteOffset := interpreterProxy stackValue: 1.
  	rcvr := interpreterProxy stackValue: 2.
  	((interpreterProxy isIntegerObject: valueArg)
  	and: [((value := interpreterProxy integerValueOf: valueArg) between: 0 and: 65535)
  	and: [interpreterProxy isIntegerObject: byteOffset]]) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self ffiAddressOf: rcvr startingAt: (interpreterProxy integerValueOf: byteOffset) size: (self sizeof: #short))
  		ifNil: [^interpreterProxy primitiveFailFor: PrimErrBadIndex]
  		ifNotNil:
  			[:addr|
  			interpreterProxy unalignedShortAt: addr put: value.
  			^interpreterProxy methodReturnValue: valueArg]!

Item was removed:
- VMStructType subclass: #ThreadedFFIX64SixteenByteReturnDD
- 	instanceVariableNames: 'a b'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-FFI'!
- 
- !ThreadedFFIX64SixteenByteReturnDD commentStamp: 'nice 1/25/2020 17:43' prior: 0!
- A ThreadedFFIX64SixteenByteReturnDD is a stub for returning a struct by value through 2 eight-byte float registers
- That is (XMM0 XMM1) on X64.
- 
- Instance Variables
- 	a:		<Object> 
- 	b:		<Object> 
- 
- a
- 	- stub for first eighbyte
- 
- b
- 	- stub for second eighbyte
- !

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
- 
- 	aBinaryBlock value: 'a' value: #double.
- 	aBinaryBlock value: 'b' value: #double.!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD class>>structTypeName (in category 'translation') -----
- structTypeName
- 	^'SixteenByteReturnDD'!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD>>a (in category 'accessing') -----
- a
- 
- 	^ a!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD>>a: (in category 'accessing') -----
- a: anObject
- 
- 	^a := anObject!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD>>b (in category 'accessing') -----
- b
- 
- 	^ b!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDD>>b: (in category 'accessing') -----
- b: anObject
- 
- 	^b := anObject!

Item was removed:
- VMStructType subclass: #ThreadedFFIX64SixteenByteReturnDI
- 	instanceVariableNames: 'a b'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-FFI'!
- 
- !ThreadedFFIX64SixteenByteReturnDI commentStamp: 'nice 1/25/2020 17:44' prior: 0!
- A ThreadedFFIX64SixteenByteReturnDI is a stub for returning a struct by value through 1 eight-byte float register and 1 eight-byte int register
- That is (XMM0 RAX) on X64.
- 
- Instance Variables
- 	a:		<Object> 
- 	b:		<Object> 
- 
- a
- 	- stub for first eighbyte
- 
- b
- 	- stub for second eighbyte
- !

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
- 
- 	aBinaryBlock value: 'a' value: #double.
- 	aBinaryBlock value: 'b' value: #sqInt.!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI class>>structTypeName (in category 'translation') -----
- structTypeName
- 	^'SixteenByteReturnDI'!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI>>a (in category 'accessing') -----
- a
- 
- 	^ a!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI>>a: (in category 'accessing') -----
- a: anObject
- 
- 	^a := anObject!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI>>b (in category 'accessing') -----
- b
- 
- 	^ b!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnDI>>b: (in category 'accessing') -----
- b: anObject
- 
- 	^b := anObject!

Item was removed:
- VMStructType subclass: #ThreadedFFIX64SixteenByteReturnID
- 	instanceVariableNames: 'a b'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-FFI'!
- 
- !ThreadedFFIX64SixteenByteReturnID commentStamp: 'nice 1/25/2020 17:45' prior: 0!
- A ThreadedFFIX64SixteenByteReturnID is a stub for returning a struct by value through 1 eight-byte int register and 1 eight-byte float register
- That is (RAX XMM0) on X64.
- 
- Instance Variables
- 	a:		<Object> 
- 	b:		<Object> 
- 
- a
- 	- stub for first eighbyte
- 
- b
- 	- stub for second eighbyte
- !

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
- 
- 	aBinaryBlock value: 'a' value: #sqInt.
- 	aBinaryBlock value: 'b' value: #double.!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID class>>structTypeName (in category 'translation') -----
- structTypeName
- 	^'SixteenByteReturnID'!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID>>a (in category 'accessing') -----
- a
- 
- 	^ a!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID>>a: (in category 'accessing') -----
- a: anObject
- 
- 	^a := anObject!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID>>b (in category 'accessing') -----
- b
- 
- 	^ b!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnID>>b: (in category 'accessing') -----
- b: anObject
- 
- 	^b := anObject!

Item was removed:
- VMStructType subclass: #ThreadedFFIX64SixteenByteReturnII
- 	instanceVariableNames: 'a b'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-FFI'!
- 
- !ThreadedFFIX64SixteenByteReturnII commentStamp: 'nice 1/25/2020 17:44' prior: 0!
- A ThreadedFFIX64SixteenByteReturnII is a stub for returning a struct by value through 2 eight-byte int registers
- That is (RAX RDX) on X64.
- 
- Instance Variables
- 	a:		<Object> 
- 	b:		<Object> 
- 
- a
- 	- stub for first eighbyte
- 
- b
- 	- stub for second eighbyte
- !

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BlockStart struct."
- 
- 	aBinaryBlock value: 'a' value: #sqInt.
- 	aBinaryBlock value: 'b' value: #sqInt.!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII class>>structTypeName (in category 'translation') -----
- structTypeName
- 	^'SixteenByteReturnII'!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII>>a (in category 'accessing') -----
- a
- 
- 	^ a!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII>>a: (in category 'accessing') -----
- a: anObject
- 
- 	^a := anObject!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII>>b (in category 'accessing') -----
- b
- 
- 	^ b!

Item was removed:
- ----- Method: ThreadedFFIX64SixteenByteReturnII>>b: (in category 'accessing') -----
- b: anObject
- 
- 	^b := anObject!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin class>>ancilliaryClasses (in category 'translation') -----
  ancilliaryClasses
  	^super ancilliaryClasses,
+ 	  { ThreadedFFI64Bit16ByteReturnDD.
+ 		ThreadedFFI64Bit16ByteReturnDI.
+ 		ThreadedFFI64Bit16ByteReturnID.
+ 		ThreadedFFI64Bit16ByteReturnII }!
- 	  { ThreadedFFIX64SixteenByteReturnDD.
- 		ThreadedFFIX64SixteenByteReturnDI.
- 		ThreadedFFIX64SixteenByteReturnID.
- 		ThreadedFFIX64SixteenByteReturnII }!




More information about the Vm-dev mailing list