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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 28 03:25:21 UTC 2021


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

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

Name: VMMaker.oscog-eem.3005
Author: eem
Time: 27 July 2021, 8:25:12.753611 pm
UUID: 7c1d4270-1771-487d-8fe6-bcef9b37c061
Ancestors: VMMaker.oscog-dtl.3004

Do much more <inline: #always> inlining in the FFI plugin, as much to get rid of unused static functions as anything else.

=============== Diff against VMMaker.oscog-dtl.3004 ===============

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  	"Answer if a struct result of a given size is returned in registers or not."
+ 	<inline: #always>
  	^returnStructSize <= self wordSize!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to true if returning the struct via register"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
  ffiPushPointer: pointer in: calloutState
  	<var: #pointer type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushSignedByte:in: (in category 'marshalling') -----
  ffiPushSignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushSignedChar:in: (in category 'marshalling') -----
  ffiPushSignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #sqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < (NumIntRegArgs - 1)
  		ifTrue:
  			[calloutState integerRegisterIndex: (calloutState integerRegisterIndex + 1 bitClear: 1).
  			 calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #usqInt).
  			 calloutState integerRegisters at: calloutState integerRegisterIndex + 1 put: (self cCoerceSimple: value >> 32 to: #usqInt).
  			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 2]
  		ifFalse:
  			[calloutState currentArg + 8 > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
  			 calloutState integerRegisterIndex: NumIntRegArgs.
  			 interpreterProxy
  				longAt: calloutState currentArg put: (self cCoerceSimple: value to: #usqInt);
  				longAt: calloutState currentArg + self wordSize put: (self cCoerceSimple: value >> 32 to: #usqInt).
  			 calloutState currentArg: calloutState currentArg + 8].
  	^0!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushSignedShort:in: (in category 'marshalling') -----
  ffiPushSignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>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: #'sqInt *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	| availableRegisterSpace stackPartSize roundedSize |
  
  	availableRegisterSpace := (NumIntRegArgs - calloutState integerRegisterIndex) * 4.
  	stackPartSize := structSize.
  	availableRegisterSpace > 0
  		ifTrue: 
  			[structSize <= availableRegisterSpace
  				ifTrue:
  					["all in registers"
  					 stackPartSize := 0.
  					 self 
  						memcpy: (self cCoerceSimple: (self addressOf: (calloutState integerRegisters at: calloutState integerRegisterIndex)) to: 'void *') 
  						_: pointer 
  						_: structSize.
  					 calloutState integerRegisterIndex: calloutState integerRegisterIndex + (structSize + 3 bitShift: -2) ]
  				ifFalse:
  					["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].
  					calloutState integerRegisterIndex: NumIntRegArgs]].
  
  	stackPartSize > 0
  		ifTrue: 
  			[roundedSize := stackPartSize + 3 bitClear: 3.
  			 calloutState currentArg + roundedSize > calloutState limit ifTrue:
  				 [^FFIErrorCallFrameTooBig].
  			 self memcpy: calloutState currentArg _: (self addressOf: ((self cCoerceSimple: pointer to: 'char *') at: availableRegisterSpace)) _: stackPartSize.
  			 calloutState currentArg: calloutState currentArg + roundedSize].
  	^0!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushUnsignedByte:in: (in category 'marshalling') -----
  ffiPushUnsignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushUnsignedChar:in: (in category 'marshalling') -----
  ffiPushUnsignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!
- 	^0
- 
- !

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushUnsignedLongLong:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < (NumIntRegArgs - 1)
  		ifTrue:
  			[calloutState integerRegisterIndex: (calloutState integerRegisterIndex + 1 bitClear: 1).
  			 calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #usqInt).
  			 calloutState integerRegisters at: calloutState integerRegisterIndex + 1 put: (self cCoerceSimple: value >> 32 to: #usqInt).
  			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 2]
  		ifFalse:
  			[calloutState currentArg + 8 > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
  			 calloutState integerRegisterIndex: NumIntRegArgs.
  			 interpreterProxy
  				longAt: calloutState currentArg put: (self cCoerceSimple: value to: #usqInt);
  				longAt: calloutState currentArg + self wordSize put: (self cCoerceSimple: value >> 32 to: #usqInt).
  			 calloutState currentArg: calloutState currentArg + 8].
+ 	^0!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiPushUnsignedShort:in: (in category 'marshalling') -----
  ffiPushUnsignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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 changed:
  ----- Method: ThreadedARM32FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
+ 	"Return through register if structReturnType is true"
- 	"Return thrue register if structReturnType is true"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  	"Answer if a struct result of a given size is able to be returned in registers.
  	NB: this is a predicate!! #canReturnInRegistersStructOfSize: does NOT return a struct in anything!!"
+ 	<inline: #always>
  	^returnStructSize <= (2 * self wordSize)!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to true if returning the struct via register"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #sqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
  	^0!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>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>
- 	<inline: true>
  	| 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 memcpy: calloutState currentArg _: (self addressOf: ((self cCoerceSimple: pointer to: #'char *') at: availableRegisterSpace)) _: stackPartSize.
  		 calloutState currentArg: calloutState currentArg + roundedSize].
  	^0!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!
- 	^0
- 
- !

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushUnsignedLongLong:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	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].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
+ 	^0!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>mustReturnStructOnStack: (in category 'marshalling') -----
  mustReturnStructOnStack: returnStructSize
  	"Answer if a struct result of a given size is unable to be returned in registers."
+ 	<inline: #always>
  	^returnStructSize > (2 * self wordSize)!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
+ 	"Return through register if structReturnType is true"
- 	"Return thrue register if structReturnType is true"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set a variable encoding how the struct is to be returned.
  	It is an OS dependent encoding, leaved to subclass responsibility."
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility
  	!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiAtomicArgByReference:Class:in: (in category 'callout support') -----
  ffiAtomicArgByReference: oop Class: oopClass in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Support for generic callout. Prepare a pointer reference to an atomic type for callout.
  	 Note: 
  		for type 'void*' we allow ByteArray/String/Symbol, wordVariableSubclass, Alien or ExternalAddress.
  		for other types we allow ByteArray, wordVariableSubclass, Alien or ExternalAddress."
  	| atomicType isString argIsAlien |
+ 	<inline: #always>
- 	<inline: true>
  	atomicType := self atomicTypeOf: calloutState ffiArgHeader.
  	(atomicType = FFITypeBool) ifTrue: "No bools on input"
  		[^FFIErrorCoercionFailed].
  	argIsAlien := (isString := interpreterProxy 
  								includesBehavior: oopClass 
  								ThatOf: interpreterProxy classString)
  					ifTrue: [false]
  					ifFalse:
  						[interpreterProxy 
  							includesBehavior: oopClass 
  							ThatOf: interpreterProxy classAlien].
  	((atomicType >> 1) = (FFITypeSignedChar >> 1)) ifTrue:"string value (char*)"
  		"note: the only types allowed for passing into char* types are
  		ByteArray, String, Symbol, Alien and *no* other byte indexed objects
  		(e.g., CompiledMethod, LargeInteger). We only check for strings
  		here and fall through to the byte* check otherwise."
  		[isString ifTrue:"String/Symbol"
  			"Strings must be allocated by the ffi support code"
  			[^self ffiPushString: (interpreterProxy firstIndexableField: oop)
  				OfLength: (interpreterProxy byteSizeOf: oop)
  				in: calloutState].
  		"Fall through to byte* test"
  		atomicType := FFITypeUnsignedByte].
  
  	self cppIf: COGMTVM ifTrue:
  	["Since all the following pass the address of the first indexable field we need to fail
  	 the call if it is threaded and the object is young, since it may move during the call."
  	((calloutState callFlags anyMask: FFICallFlagThreaded)
  	and: [(argIsAlien not or: [self isDirectAlien: oop])
  	and: [interpreterProxy isYoung: oop]]) ifTrue:
  		[^PrimErrObjectMayMove negated]].
  
  	(atomicType = FFITypeVoid or:[(atomicType >> 1) = (FFITypeSignedByte >> 1)]) ifTrue:
  		"byte* -- see comment on string above"
  		[(isString or: [oopClass = interpreterProxy classByteArray]) ifTrue: "String/Symbol/ByteArray"
  			[^self ffiPushPointer: (interpreterProxy firstIndexableField: oop) in: calloutState].
  		(oopClass = interpreterProxy classExternalAddress) ifTrue: 
  			[^self ffiPushPointer: (self longAt: oop + interpreterProxy baseHeaderSize) in: calloutState].
  		argIsAlien ifTrue:
  			[^self ffiPushPointer: (self pointerForOop: (self startOfData: oop)) in: calloutState].
  		atomicType = FFITypeVoid ifFalse:
  			[^FFIErrorCoercionFailed]].
  		"note: type void falls through"
  
  	"I can push pointers to any type (take for instance calls who receive int* output arguments, etc.)
  	 but I need to store them into a ByteArray, ExternalAddress or Alien"
  	(atomicType <= FFITypeDoubleFloat) ifTrue:
  		[((interpreterProxy isWords: oop) or: [oopClass = interpreterProxy classByteArray]) ifTrue:
  			[^self ffiPushPointer: (interpreterProxy firstIndexableField: oop) in: calloutState].
  		(oopClass = interpreterProxy classExternalAddress) ifTrue: 
  			[^self ffiPushPointer: (self longAt: oop + interpreterProxy baseHeaderSize) in: calloutState].
  		argIsAlien ifTrue:
  			[^self ffiPushPointer: (self pointerForOop: (self startOfData: oop)) in: calloutState]].
  
  	^FFIErrorCoercionFailed!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiAtomicStructByReference:Class:in: (in category 'callout support') -----
  ffiAtomicStructByReference: oop Class: oopClass in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Support for generic callout. Prepare an external pointer reference to an atomic type for callout."
  	| atomicType err valueOop |
+ 	<inline: #always>
- 	<inline: true>
  	"must be external data to pass pointers to atomic type"
  	oopClass = interpreterProxy classExternalData 
  		ifFalse:[^FFIErrorCoercionFailed].
  	atomicType := self atomicTypeOf: calloutState ffiArgHeader.
  	"no type checks for void pointers"
  	atomicType ~= FFITypeVoid ifTrue:[
  		err := self ffiValidateExternalData: oop AtomicType: atomicType.
  		err ~= 0 ifTrue:[^err].
  	].
  	"and push pointer contents"
  	valueOop := interpreterProxy fetchPointer: 0 ofObject: oop.
  	^self ffiPushPointerContentsOf: valueOop in: calloutState!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiContentsOfHandle:errCode: (in category 'callout support') -----
  ffiContentsOfHandle: oop errCode: errCode
  	"Make sure that the given oop is a valid external handle"
+ 	<inline: #always>
- 	<inline: true>
  	((interpreterProxy isBytes: oop)
  	 and: [(interpreterProxy byteSizeOf: oop) = (self sizeof: #sqInt)]) ifFalse:
  		[^self ffiFail: errCode].
  	^interpreterProxy fetchPointer: 0 ofObject: oop!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCreateIntegralResultOop:ofAtomicType:in: (in category 'callout support') -----
  ffiCreateIntegralResultOop: retVal ofAtomicType: atomicType in: calloutState
+ 	<inline: #always>
- 	<inline: true>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #retVal type: #usqLong>
  	"Callout support. Return the appropriate oop for the given atomic type"
  	| shift value mask byteSize |
  	<var: 'value' type: #usqLong>
  	<var: 'mask' type: #usqLong>
  	self assert: atomicType < FFITypeSingleFloat.
  
  	atomicType = FFITypeBool ifTrue:
  		["Make sure bool honors the byte size requested"
  		 byteSize := calloutState ffiRetHeader bitAnd: FFIStructSizeMask.
  		 value := byteSize = (self sizeof: retVal)
  					ifTrue:[retVal]
  					ifFalse:[retVal bitAnd: 1 asUnsignedLongLong << (byteSize * 8) - 1].
  		 ^value = 0
  			ifTrue:[interpreterProxy falseObject]
  			ifFalse:[interpreterProxy trueObject]].
  	atomicType <= FFITypeSignedInt ifTrue:
  		["these are all generall integer returns"
  		atomicType <= (BytesPerWord = 8 ifTrue: [FFITypeSignedInt] ifFalse: [FFITypeSignedShort]) ifTrue:
  			["byte/short. first extract partial word, then sign extend"
  			shift := (BytesPerWord = 8 and: [atomicType >= FFITypeUnsignedInt])
  						ifTrue: [32]
  						ifFalse: [(atomicType >> 1) * 8]. "# of significant bits"
  			value := retVal bitAnd: (1 asUnsignedLongLong << shift - 1). 
  			(atomicType anyMask: 1) ifTrue:
  				["make the guy signed"
  				mask := 1 asUnsignedLongLong << (shift-1).
  				value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  			^interpreterProxy integerObjectOf: value].
  		"Word sized integer return"
  		^(atomicType anyMask: 1)
  			ifTrue:[interpreterProxy signedMachineIntegerFor: retVal] "signed return"
  			ifFalse:[interpreterProxy positiveMachineIntegerFor: retVal]]. "unsigned return"
  
  	"longlong, char"
  	(atomicType >> 1) = (FFITypeSignedLongLong >> 1) ifTrue:
  		[^(atomicType anyMask: 1)
  			ifTrue: [interpreterProxy signed64BitIntegerFor: retVal] "signed return"
  			ifFalse: [interpreterProxy positive64BitIntegerFor: retVal]].
  	self cppIf: #SPURVM
  		ifTrue: [^interpreterProxy characterObjectOf: (retVal bitAnd: 16r3FFFFFFF)]
  		ifFalse: [^interpreterProxy characterObjectOf: (retVal bitAnd: 16rFF)]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiFloatValueOf: (in category 'callout support') -----
  ffiFloatValueOf: oop
  	"Support for generic callout. Return a float value that is coerced as C would do."
  	<returnTypeC: #double>
+ 	<inline: #always>
  	(interpreterProxy isFloatObject: oop) ifTrue:
  		[^interpreterProxy floatValueOf: oop].
  	"otherwise try the integer coercions and return its float value"
  	^(self ffiIntegerValueOf: oop) asFloat!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiLoadCalloutAddress: (in category 'symbol loading') -----
  ffiLoadCalloutAddress: lit
  	"Load the address of the foreign function from the given object"
+ 	<inline: #always>
  	| addressPtr address ptr |
  	<var: #ptr type: #'sqIntptr_t *'>
  	"Lookup the address"
  	addressPtr := interpreterProxy fetchPointer: 0 ofObject: lit.
  	"Make sure it's an external handle"
  	address := self ffiContentsOfHandle: addressPtr errCode: FFIErrorBadAddress.
  	interpreterProxy failed ifTrue:
  		[^0].
  	address = 0 ifTrue:"Go look it up in the module"
  		[self externalFunctionHasStackSizeSlot ifTrue:
  			[interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: lit withValue: -1].
  		(interpreterProxy slotSizeOf: lit) < 5 ifTrue:
  			[^self ffiFail: FFIErrorNoModule].
  		address := self ffiLoadCalloutAddressFrom: lit.
  		interpreterProxy failed ifTrue:
  			[^0].
  		"Store back the address"
  		ptr := interpreterProxy firstIndexableField: addressPtr.
  		ptr at: 0 put: address].
  	^address!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushDoubleFloat:in: (in category 'marshalling') -----
  ffiPushDoubleFloat: value in: calloutState
  	<var: #calloutState type: #double>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
  ffiPushPointer: pointer in: calloutState
  	<var: #pointer type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedByte:in: (in category 'marshalling') -----
  ffiPushSignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedChar:in: (in category 'marshalling') -----
  ffiPushSignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #sqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedLongLongOop:in: (in category 'marshalling') -----
  ffiPushSignedLongLongOop: oop in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	"Push a longlong type (e.g., a 64bit integer).
  	Note: Coercions from float are *not* supported."
  	| value |
  	<var: #value type: #sqLong>
  	(oop = interpreterProxy nilObject
  	 or: [oop = interpreterProxy falseObject])
  		ifTrue:[value := 0] ifFalse:
  	[oop = interpreterProxy trueObject
  		ifTrue:[value := 1] ifFalse:
  	[value := interpreterProxy signed64BitValueOf: oop.
  	 interpreterProxy failed ifTrue:
  		[^FFIErrorCoercionFailed]]].
  	^self ffiPushSignedLongLong: value in: calloutState!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSignedShort:in: (in category 'marshalling') -----
  ffiPushSignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushSingleFloat:in: (in category 'marshalling') -----
  ffiPushSingleFloat: value in: calloutState
  	<var: #value type: #float>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushString:OfLength:in: (in category 'marshalling') -----
  ffiPushString: pointer OfLength: length in: calloutState
  	<var: #pointer type: #'char *'>
  	<var: #calloutState type: #'CalloutState *'>
  	| copy |
  	<var: #copy type: #'char *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState stringArgIndex >= MaxNumArgs ifTrue:
  		[^PrimErrBadNumArgs negated].
  	copy := self malloc: length + 1.
  	copy isNil ifTrue:
  		[^PrimErrNoCMemory negated].
  	self memcpy: copy _: pointer _: length.
  	copy at: length put: 0.
  	calloutState stringArgs at: calloutState stringArgIndex put: copy.
  	calloutState stringArgIndex: calloutState stringArgIndex + 1.
  	^self ffiPushPointer: copy in: calloutState!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedByte:in: (in category 'marshalling') -----
  ffiPushUnsignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedChar:in: (in category 'marshalling') -----
  ffiPushUnsignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedLongLongOop:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLongOop: oop in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Push an unsigned longlong type (e.g., a 64bit integer).
  	Note: Coercions from float are *not* supported."
+ 	<inline: #always>
  	| value |
  	<var: #value type: #usqLong>
  	(oop = interpreterProxy nilObject
  	 or: [oop = interpreterProxy falseObject])
  		ifTrue:[value := 0] ifFalse:
  	[oop = interpreterProxy trueObject
  		ifTrue:[value := 1] ifFalse:
  	[value := interpreterProxy positive64BitValueOf: oop.
  	 interpreterProxy failed ifTrue:
  		[^FFIErrorCoercionFailed]]].
  	^self ffiPushUnsignedLongLong: value in: calloutState!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedShort:in: (in category 'marshalling') -----
  ffiPushUnsignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushVoid:in: (in category 'marshalling') -----
  ffiPushVoid: ignored in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	"This is a fallback in case somebody tries to pass a 'void' value.
  	We could simply ignore the argument but I think it's better to let
  	the caller know what he did"
  	^FFIErrorAttemptToPassVoid!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to true if returning the struct via register"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
  ffiPushPointer: pointer in: calloutState
  	<var: #pointer type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: pointer.
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSignedByte:in: (in category 'marshalling') -----
  ffiPushSignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed char').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSignedChar:in: (in category 'marshalling') -----
  ffiPushSignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed char').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: value.
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 8 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy
  		longAt: calloutState currentArg put: (self cCoerceSimple: value to: #usqInt);
  		longAt: calloutState currentArg + 4 put: (self cCoerceSimple: value >> 32 to: #usqInt).
  	calloutState currentArg: calloutState currentArg + 8.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSignedShort:in: (in category 'marshalling') -----
  ffiPushSignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed short').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>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: #'sqInt *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	| roundedSize |
  	roundedSize := structSize + 3 bitClear: 3.
  	calloutState currentArg + roundedSize > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	self memcpy: calloutState currentArg _: pointer _: structSize.
  	calloutState currentArg: calloutState currentArg + roundedSize.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsignedByte:in: (in category 'marshalling') -----
  ffiPushUnsignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned char').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsignedChar:in: (in category 'marshalling') -----
  ffiPushUnsignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned char').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: value.
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsignedLongLong:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 8 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy
  		longAt: calloutState currentArg put: (self cCoerceSimple: value to: #usqInt);
  		longAt: calloutState currentArg + 4 put: (self cCoerceSimple: value >> 32 to: #usqInt).
  	calloutState currentArg: calloutState currentArg + 8.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsignedShort:in: (in category 'marshalling') -----
  ffiPushUnsignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned short').
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
+ 	"Return through register if structReturnType is true"
- 	"Return thrue register if structReturnType is true"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  	"Answer if a struct result of a given size is returned in registers or not.
  	 The ABI spec defines return in registers, but some linux gcc versions implemented an
  	 erroneous draft which does not return any struct in memory.  Implement the SysV ABI."
+ 	<inline: #always>
  	^returnStructSize <= 8!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to true if returning the struct via register"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushDoubleFloat:in: (in category 'marshalling') -----
  ffiPushDoubleFloat: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
  ffiPushPointer: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSignedByte:in: (in category 'marshalling') -----
  ffiPushSignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSignedChar:in: (in category 'marshalling') -----
  ffiPushSignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #sqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSignedShort:in: (in category 'marshalling') -----
  ffiPushSignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushSingleFloat:in: (in category 'marshalling') -----
  ffiPushSingleFloat: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushUnsignedByte:in: (in category 'marshalling') -----
  ffiPushUnsignedByte: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushUnsignedChar:in: (in category 'marshalling') -----
  ffiPushUnsignedChar: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushUnsignedLongLong:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>ffiPushUnsignedShort:in: (in category 'marshalling') -----
  ffiPushUnsignedShort: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	self shouldBeImplemented.
  	^0!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
+ 	"Return through register if structReturnType is true"
- 	"Return thrue register if structReturnType is true"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType!

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

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

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

Item was changed:
  ----- Method: ThreadedX64FFIPlugin>>ffiPushSignedInt:in: (in category 'marshalling') -----
  ffiPushSignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < NumIntRegArgs
  		ifTrue:
  			[calloutState integerRegisters at: calloutState integerRegisterIndex put: value.
  			 calloutState incrementIntegerRegisterIndex]
  		ifFalse:
  			[calloutState currentArg + WordSize > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + WordSize].
+ 	^0!
- 	^0
- !

Item was changed:
  ----- Method: ThreadedX64FFIPlugin>>ffiPushSignedLongLong:in: (in category 'marshalling') -----
  ffiPushSignedLongLong: value in: calloutState
  	<var: #value type: #sqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < NumIntRegArgs
  		ifTrue:
  			[calloutState integerRegisters at: calloutState integerRegisterIndex put: (self cCoerceSimple: value to: #usqInt).
  			 calloutState incrementIntegerRegisterIndex]
  		ifFalse:
  			[calloutState currentArg + WordSize > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + WordSize].
  	^0!

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

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

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

Item was changed:
  ----- Method: ThreadedX64FFIPlugin>>ffiPushUnsignedInt:in: (in category 'marshalling') -----
  ffiPushUnsignedInt: value in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < NumIntRegArgs
  		ifTrue:
  			[calloutState integerRegisters at: calloutState integerRegisterIndex put: value.
  			 calloutState incrementIntegerRegisterIndex]
  		ifFalse:
  			[calloutState currentArg + WordSize > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + WordSize].
+ 	^0!
- 	^0
- 
- !

Item was changed:
  ----- Method: ThreadedX64FFIPlugin>>ffiPushUnsignedLongLong:in: (in category 'marshalling') -----
  ffiPushUnsignedLongLong: value in: calloutState
  	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	calloutState integerRegisterIndex < NumIntRegArgs
  		ifTrue:
  			[calloutState integerRegisters at: calloutState integerRegisterIndex put: value.
  			 calloutState incrementIntegerRegisterIndex]
  		ifFalse:
  			[calloutState currentArg + WordSize > calloutState limit ifTrue: [^FFIErrorCallFrameTooBig].
  			 interpreterProxy longAt: calloutState currentArg put: value.
  			 calloutState currentArg: calloutState currentArg + WordSize].
  	^0!

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

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  	"Answer if a struct result of a given size is returned in registers or not."
+ 	<inline: #always>
  	^returnStructSize <= (WordSize * 2)!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to an integer encoding the type of registers used to return the struct
  	* 2r00 for float float (XMM0 XMM1)
  	* 2r01 for int float (RAX XMM0)
  	* 2r10 for float int (XMM0 RAX)
  	* 2r11 for int int (RAX RDX)
  	* 2r100 for float (XMM0)
  	* 2r101 for int (RAX)
  	* 2r110 For return thru memory (struct field not aligned or struct too big)"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	| registerType |
  	registerType := (self canReturnInRegistersStructOfSize: calloutState structReturnSize)
  		ifTrue:
  			[ self
  				registerTypeForStructSpecs: (interpreterProxy firstIndexableField: calloutState ffiRetSpec)
  				OfLength: (interpreterProxy slotSizeOf: calloutState ffiRetSpec)]
  		ifFalse:
  			[ "We cannot return via register, struct is too big"
  			2r110 ].
  	calloutState structReturnType: registerType!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>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: #'sqInt *'>
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  	| roundedSize registerType numDoubleRegisters numIntegerRegisters passField0InXmmReg passField1InXmmReg |
  	structSize <= 16 ifTrue:
  		["See sec 3.2.3 of http://people.freebsd.org/~obrien/amd64-elf-abi.pdf. (dravft version 0.90).
  		  All of the folowing are passed in registers:
  			typedef struct { long a; } s0;
  			typedef struct { double a; } s1;
  			typedef struct { long a; double b; } s2;
  			typedef struct { int a; int b; double c; } s2a;
  			typedef struct { short a; short b; short c; short d; double e; } s2b;
  			typedef struct { long a; float b; } s2f;
  			typedef struct { long a; float b; float c; } s2g;
  			typedef struct { int a; float b; int c; float d; } s2h;"
  		 registerType := self registerTypeForStructSpecs: (self cCoerce: argSpec to: #'unsigned int *') OfLength: argSpecSize.
  		 registerType = 2r110 "check case of invalid alignment => pass by memory"
  			ifFalse: 
  				 [passField0InXmmReg := (registerType bitAnd: 1) = 0.
  				  structSize <= 8
  					ifTrue:
  						[numIntegerRegisters := registerType bitAnd: 1.
  						 numDoubleRegisters := 1 - numIntegerRegisters]
  					ifFalse:
  						[passField1InXmmReg := (registerType bitAnd: 2) = 0.
  						 numIntegerRegisters := (registerType bitAnd: 2) >> 1 + (registerType bitAnd: 1).
  						 numDoubleRegisters := 2 - numIntegerRegisters].
  				 (calloutState floatRegisterIndex + numDoubleRegisters <= NumFloatRegArgs
  				  and: [calloutState integerRegisterIndex + numIntegerRegisters <= NumIntRegArgs]) ifTrue:
  					[passField0InXmmReg
  						ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 0) in: calloutState]
  						ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 0) in: calloutState].
  					 structSize > 8 ifTrue:
  						[passField1InXmmReg
  							ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 1) in: calloutState]
  							ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 1) in: calloutState]].
  					 ^0]]].
  
  	roundedSize := structSize + 7 bitClear: 7.
  	calloutState currentArg + roundedSize > calloutState limit ifTrue:
  		 [^FFIErrorCallFrameTooBig].
  	self memcpy: calloutState currentArg _: (self cCoerceSimple: pointer to: 'char *') _: structSize.
  	calloutState currentArg: calloutState currentArg + roundedSize.
  	^0!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
  	"Use the register type encoding stored in structReturnType
  	2r110 means impossible, pass thru memory.
  	Anything smaller encodes the type of register used, thus means true."
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType < 2r110!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  	"Answer if a struct result of a given size is returned in registers or not."
+ 	<inline: #always>
  	^returnStructSize <= WordSize and: ["returnStructSize isPowerOfTwo" (returnStructSize bitAnd: returnStructSize-1) = 0]!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>encodeStructReturnTypeIn: (in category 'callout support') -----
  encodeStructReturnTypeIn: calloutState
  	"Set the return type to true if returning the struct via register"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
- 	<inline: true>
  
  	calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>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: #'sqInt *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #arg type: #usqLong>
+ 	<inline: #always>
- 	<inline: true>
  	structSize <= 0 ifTrue:
  		[^FFIErrorStructSize].
+ 
  	"See https://docs.microsoft.com/en-us/cpp/build/x64-calling-convention?view=vs-2019"
  	(structSize <= WordSize
  	 and: [(structSize bitAnd: structSize - 1) = 0 "a.k.a. structSize isPowerOfTwo"]) ifTrue:
  		[| arg |
  		self memcpy: (self addressOf: arg) _: pointer _: structSize.
  		^self ffiPushUnsignedLongLong: arg in: calloutState].
  
+ 
  	"BUG!!!! This memory should be 16-byte aligned; Spur guarantees only 8-byte alignment."
  	self flag: #bug.
  	^self ffiPushPointer: pointer in: calloutState!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
+ 	"Return through register if structReturnType is true"
- 	"Return thrue register if structReturnType is true"
  	<var: #calloutState type: #'CalloutState *'>
+ 	<inline: #always>
  	^calloutState structReturnType!



More information about the Vm-dev mailing list