VM Maker: VMMaker.oscog-nice.2690.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-nice.2690.mcz

commits-2
 
Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2690.mcz

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

Name: VMMaker.oscog-nice.2690
Author: nice
Time: 30 January 2020, 11:04:41.785937 pm
UUID: e61056e6-e4d9-4686-be96-bfcfa8f3afc2
Ancestors: VMMaker.oscog-eem.2689

Finish FFI support for returning of a packed struct by value in X64 SysV

Checking the size of a struct is not the only condition for returning a struct via registers.
Some ABI like X64 SysV also mandates that struct fields be properly aligned.
Therefore, we cannot just rely on #returnStructInRegisters:.

Rename it (and preserve timestamps by courtesy):
#returnStructInRegisters: -> #canReturnInRegistersStructOfSize:

Perform a more thorough analysis during the setup in #ffiCheckReturn:With:in:
The ABI will #encodeStructReturnTypeIn: a new callout state.
This structReturnType is telling how the struct should be returned
- via registers (and which registers)
- or via pointer to memory allocated by caller

This structReturnType will be used at time of:
- allocating the memory in caller - see #ffiCall:ArgArrayOrNil:NumArgs:
- dispatching to the correct FFI prototype - see ThreadedX64SysVFFIPlugin>>#ffiCalloutTo:SpecOnStack:in:
- copying back the struct contents to ExternalStructure handle (a ByteArray) - see #ffiReturnStruct:ofType:in:

Since structReturnType is encoded, it is not necessarily accessed directly, but rather via new implementation of #returnStructInRegisters: whch now takes the calloutState and knows how to decode its structReturnType.

TO DO (reminder):
The analysis of structReturnType is not necessarily cheap and should better be cached in some unused bits of compiledSpec literal.
This cache shall be cleaned up when restarting the image on a different OS.

TO DO (reminder):
Not all composite are struct, we should also handle Unions!

TO DO (reminder):
Other ABI like IA32 also fails the new test in SysV, that should be fixed too.

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

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

Item was added:
+ ----- 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: true>
+
+ calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>ffiReturnStruct:ofType:in: (in category 'callout support') -----
  ffiReturnStruct: longLongRetPtr ofType: ffiRetType in: calloutState
  <var: #longLongRetPtr type: #'void *'>
  <var: #calloutState type: #'CalloutState *'>
  "Create a structure return value from an external function call.  The value has been stored in
  alloca'ed space pointed to by the calloutState or in the return value passed by pointer."
  | retOop retClass oop |
  <inline: true>
  retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.
  retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.
  self remapOop: retOop
  in: [oop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: calloutState structReturnSize].
  self memcpy: (interpreterProxy firstIndexableField: oop)
+ _: ((self returnStructInRegisters: calloutState)
- _: ((self returnStructInRegisters: calloutState structReturnSize)
  ifTrue: [longLongRetPtr]
  ifFalse: [calloutState limit])
  _: calloutState structReturnSize.
  interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
  ^retOop!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Return thrue register if structReturnType is true"
+ <var: #calloutState type: #'CalloutState *'>
+ ^calloutState structReturnType!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory or not."
- ^returnStructSize <= self wordSize!

Item was added:
+ ----- 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!!"
+ ^returnStructSize <= (2 * self wordSize)!

Item was added:
+ ----- 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: true>
+
+ calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

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 x1Ret |
  <var: #floatRet type: #double>
  <var: #intRet type: #usqLong>
  <var: #x1Ret type: #usqLong>
  <inline: true>
  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) ifTrue:
  [atomicType = FFITypeSingleFloat
  ifTrue:
  [floatRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(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)]
  ifFalse: "atomicType = FFITypeDoubleFloat"
  [floatRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(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.
 
  ^interpreterProxy floatObjectOf: floatRet].
 
  "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: [
  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:
- and: [self returnStructInRegisters: calloutState structReturnSize]) 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 addressOf: intRet) ofType: (self ffiReturnType: specOnStack) in: calloutState].
 
  ^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiReturnStruct:ofType:in: (in category 'callout support') -----
  ffiReturnStruct: longLongRetPtr ofType: ffiRetType in: calloutState
  <var: #longLongRetPtr type: #'void *'>
  <var: #calloutState type: #'CalloutState *'>
  "Create a structure return value from an external function call.  The value has been stored in
  alloca'ed space pointed to by the calloutState or in the integer registers."
  | retOop retClass oop |
  <inline: true>
  retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.
  retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.
  self remapOop: retOop
  in: [oop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: calloutState structReturnSize].
  self memcpy: (interpreterProxy firstIndexableField: oop)
+ _: ((self returnStructInRegisters: calloutState)
- _: ((self returnStructInRegisters: calloutState structReturnSize)
  ifTrue: [self addressOf: calloutState integerRegisters]
  ifFalse: [calloutState limit])
  _: calloutState structReturnSize.
  interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
  ^retOop!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Return thrue register if structReturnType is true"
+ <var: #calloutState type: #'CalloutState *'>
+ ^calloutState structReturnType!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is able to be returned in registers.
- NB: this is a predicate!! #returnStructInRegisters: does NOT return a struct in anything!!"
- ^returnStructSize <= (2 * self wordSize)!

Item was changed:
  VMStructType subclass: #ThreadedFFICalloutState
+ instanceVariableNames: 'argVector currentArg limit structReturnSize structReturnType callFlags ffiArgSpec ffiArgSpecSize ffiArgHeader ffiRetHeader ffiRetSpec stringArgIndex stringArgs'
- instanceVariableNames: 'argVector currentArg limit structReturnSize callFlags ffiArgSpec ffiArgSpecSize ffiArgHeader ffiRetHeader ffiRetSpec stringArgIndex stringArgs'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-Plugins-FFI'!
 
+ !ThreadedFFICalloutState commentStamp: 'nice 1/30/2020 21:13' prior: 0!
- !ThreadedFFICalloutState commentStamp: '<historical>' prior: 0!
  Instances of the receiver hold the per-thread state of a call-out.
 
  long *argVector pointer to the start of the alloca'ed argument marshalling area
  long *currentArg pointer to the position in argVector to write the current argument
  long *limit the limit of the argument marshalling area (for bounds checking)
  structReturnSize the size of the space allocated for the structure return, if any
+ structReturnType an integer encoding how the struct is returned (typically via registers or pointer to allocated memory)
  callFlags the value of the ExternalFunctionFlagsIndex field in the ExternalFunction being called
  ffiArgSpec et al type information for the current argument being marshalled
  stringArgIndex the count of temporary strings used for marshalling Smalltalk strings to character strings.
  stringArgs pointers to the temporary strings used for marshalling Smalltalk strings to character strings.!

Item was added:
+ ----- Method: ThreadedFFICalloutState>>structReturnType (in category 'accessing') -----
+ structReturnType
+ "Answer the value of structReturnType
+ It is an OS dependent field encoding for example if struct are to be returned
+ - via register
+ - via pointer to memory allocated by caller"
+
+ ^ structReturnType!

Item was added:
+ ----- Method: ThreadedFFICalloutState>>structReturnType: (in category 'accessing') -----
+ structReturnType: anObject
+ "Set the value of structReturnType"
+
+ ^structReturnType := anObject!

Item was added:
+ ----- Method: ThreadedFFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
+ canReturnInRegistersStructOfSize: returnStructSize
+ "Answer if a struct result of a given size can be returned via registers or not.
+ Size is a necessary condition, but it might not be a sufficient condition.
+ For example, SysV X64 also require that struct fields be properly aligned."
+ ^self subclassResponsibility!

Item was added:
+ ----- 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: true>
+ self subclassResponsibility
+ !

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

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCheckReturn:With:in: (in category 'callout support') -----
  ffiCheckReturn: retSpec With: retClass in: calloutState
  <var: #calloutState type: #'CalloutState *'>
  "Make sure we can return an object of the given type"
  <inline: true>
  retClass = interpreterProxy nilObject ifFalse:
  [(interpreterProxy
  includesBehavior: retClass
  ThatOf: interpreterProxy classExternalStructure) ifFalse:
  [^FFIErrorBadReturn]].
 
  ((interpreterProxy isWords: retSpec)
  and: [(interpreterProxy slotSizeOf: retSpec) > 0]) ifFalse:
  [^FFIErrorWrongType].
 
  calloutState ffiRetSpec: retSpec.
  calloutState ffiRetHeader: (interpreterProxy fetchLong32: 0 ofObject: retSpec).
  (self isAtomicType: calloutState ffiRetHeader) ifFalse:
  [retClass = interpreterProxy nilObject ifTrue:
  [^FFIErrorBadReturn]].
  (calloutState ffiRetHeader bitAnd: (FFIFlagPointer bitOr: FFIFlagStructure)) = FFIFlagStructure ifTrue:
+ [calloutState structReturnSize: (calloutState ffiRetHeader bitAnd: FFIStructSizeMask).
+ self encodeStructReturnTypeIn: calloutState].
- [calloutState structReturnSize: (calloutState ffiRetHeader bitAnd: FFIStructSizeMask)].
  ^0!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Answer if struct result is returned in registers or not.
+ Use the OS specific encoding stored in structReturnType.
+ Since it is OS dependent, leave the responsibility to subclass"
+ <var: #calloutState type: #'CalloutState *'>
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory or not."
  ^self subclassResponsibility!

Item was added:
+ ----- Method: ThreadedIA32FFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
+ canReturnInRegistersStructOfSize: returnStructSize
+ "Answer if a struct result of a given size is returned in registers or not."
+ <cmacro: '(sz) (WIN32_X86_STRUCT_RETURN && (sz) <= 8 && !!((sz)&((sz)-1)))'>
+ ^returnStructSize <= 8 and: [returnStructSize isPowerOfTwo]!

Item was added:
+ ----- 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: true>
+
+ calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiReturnStruct:ofType:in: (in category 'callout support') -----
  ffiReturnStruct: longLongRetPtr ofType: ffiRetType in: calloutState
  <var: #longLongRetPtr type: #'void *'>
  <var: #calloutState type: #'CalloutState *'>
  "Create a structure return value from an external function call.  The value as been stored in
  alloca'ed space pointed to by the calloutState or in the return value passed by pointer."
  | retOop retClass oop |
  <inline: true>
  retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.
  retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.
  self remapOop: retOop
  in: [oop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: calloutState structReturnSize].
  self memcpy: (interpreterProxy firstIndexableField: oop)
+ _: ((self returnStructInRegisters: calloutState)
- _: ((self returnStructInRegisters: calloutState structReturnSize)
  ifTrue: [longLongRetPtr]
  ifFalse: [calloutState limit])
  _: calloutState structReturnSize.
  interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
  ^retOop!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Return thrue register if structReturnType is true"
+ <var: #calloutState type: #'CalloutState *'>
+ ^calloutState structReturnType!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory or not."
- <cmacro: '(sz) (WIN32_X86_STRUCT_RETURN && (sz) <= 8 && !!((sz)&((sz)-1)))'>
- ^returnStructSize <= 8 and: [returnStructSize isPowerOfTwo]!

Item was added:
+ ----- 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."
+ ^returnStructSize <= 8!

Item was added:
+ ----- 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: true>
+
+ calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedPPCBEFFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Return thrue register if structReturnType is true"
+ <var: #calloutState type: #'CalloutState *'>
+ ^calloutState structReturnType!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory 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."
- ^returnStructSize <= 8!

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

Item was added:
+ ----- 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: 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>>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 sddRet sdiRet sidRet siiRet returnStructByValue registerType sRetPtr |
  <var: #floatRet type: #double>
  <var: #intRet type: #sqInt>
  <var: #siiRet type: #SixteenByteReturnII>
  <var: #sidRet type: #SixteenByteReturnID>
  <var: #sdiRet type: #SixteenByteReturnDI>
  <var: #sddRet type: #SixteenByteReturnDD>
  <var: #sRetPtr type: #'void *'>
  <inline: true>
 
  returnStructByValue := (calloutState ffiRetHeader bitAnd: FFIFlagStructure + FFIFlagPointer + FFIFlagAtomic) = FFIFlagStructure.
- returnStructByValue
- ifTrue:
- [(self returnStructInRegisters: calloutState structReturnSize)
- ifTrue: [registerType := self registerTypeForStructSpecs: (interpreterProxy firstIndexableField: calloutState ffiRetSpec) OfLength: (interpreterProxy slotSizeOf: calloutState ffiRetSpec)]
- ifFalse: [registerType := 2r110 "cannot pass by register"]].
 
  myThreadIndex := interpreterProxy disownVM: (self disownFlagsFor: calloutState).
 
  calloutState floatRegisterIndex > 0 ifTrue:
  [self
  load: (calloutState floatRegisters at: 0)
  Flo: (calloutState floatRegisters at: 1)
  a: (calloutState floatRegisters at: 2)
  t: (calloutState floatRegisters at: 3)
  R: (calloutState floatRegisters at: 4)
  e: (calloutState floatRegisters at: 5)
  g: (calloutState floatRegisters at: 6)
  s: (calloutState floatRegisters at: 7)].
 
  (self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  [self setsp: calloutState argVector].
 
  atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  (atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:
  [atomicType = FFITypeSingleFloat
  ifTrue:
  [floatRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(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)]
  ifFalse: "atomicType = FFITypeDoubleFloat"
  [floatRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(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)].
 
  interpreterProxy ownVM: myThreadIndex.
 
  ^interpreterProxy floatObjectOf: floatRet].
 
  returnStructByValue  ifFalse:
  [intRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(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).
  interpreterProxy ownVM: myThreadIndex.
  (calloutState ffiRetHeader anyMask: FFIFlagPointer) ifTrue:
  [^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  ^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState].
 
+ registerType := calloutState structReturnType.
  registerType
  caseOf:
  {[2r00] ->
  [sddRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnDD (*)(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).
  sRetPtr := (self addressOf: sddRet) asVoidPointer].
  [2r01] ->
  [sidRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnID (*)(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).
  sRetPtr := (self addressOf: sidRet) asVoidPointer].
  [2r10] ->
  [sdiRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnDI (*)(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).
  sRetPtr := (self addressOf: sdiRet) asVoidPointer].
  [2r11] ->
  [siiRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnII (*)(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).
  sRetPtr := (self addressOf: siiRet) asVoidPointer].
  [2r100] ->
  [floatRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(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).
  sRetPtr := (self addressOf: floatRet) asVoidPointer].
  [2r101] ->
  [intRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(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).
  sRetPtr := (self addressOf: intRet) asVoidPointer].
  [2r110] ->
  ["return a pointer to alloca'd memory"
  intRet := self
  dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(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).
  sRetPtr := intRet asVoidPointer "address of struct is returned in RAX, which also is calloutState limit"]}
  otherwise:
  [interpreterProxy ownVM: myThreadIndex.
  self ffiFail: FFIErrorWrongType. ^nil].
 
  interpreterProxy ownVM: myThreadIndex.
  ^self ffiReturnStruct: sRetPtr ofType: (self ffiReturnType: specOnStack) in: calloutState!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>registerTypeForStructSpecs:OfLength: (in category 'marshalling') -----
  registerTypeForStructSpecs: specs OfLength: specSize
  "Answer with a number characterizing the register type for passing a struct of size <= 16 bytes.
  The bit at offset i of registerType is set to 1 if eightbyte at offset i is a int register (RAX ...)
  The bit at offset 2 indicates if there is a single eightbyte (struct size <= 8)
  * 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 INVALID (not aligned)
  Beware, the bits must be read from right to left for decoding register type.
  Note: this method reconstructs the struct layout according to X64 alignment rules.
  Therefore, it will not work for packed struct or other exotic alignment."
 
  <var: #specs type: #'unsigned int*'>
  <var: #subIndex type: #'unsigned int'>
+ <inline: false>
  | eightByteOffset byteOffset index registerType spec fieldSize alignment atomic subIndex isInt |
  index := 0.
  (self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)
  ifFalse: [^2r110].
  eightByteOffset := 0.
  byteOffset := 0.
  registerType := ((specs at: index) bitAnd: FFIStructSizeMask) <= 8 ifTrue: [2r100] ifFalse: [0].
  [(index := index + 1) < specSize]
  whileTrue:
  [spec := specs at: index.
  isInt := false.
  spec = FFIFlagStructure "this marks end of structure and should be ignored"
  ifFalse:
  [(spec anyMask: FFIFlagPointer)
  ifTrue:
  [fieldSize := BytesPerWord.
  alignment := fieldSize.
  isInt := true]
  ifFalse:
  [(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
  caseOf:
  {[FFIFlagStructure] ->
  [fieldSize := 0.
  subIndex := index.
  alignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: subIndex)].
  [FFIFlagAtomic] ->
  [fieldSize := spec bitAnd: FFIStructSizeMask.
  alignment := fieldSize.
  atomic := self atomicTypeOf: spec.
  isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
  otherwise: ["invalid spec" ^-1]].
  (byteOffset bitAnd: alignment - 1) = 0
  ifFalse:
  ["this field requires alignment"
  byteOffset := (byteOffset bitClear: alignment - 1) + alignment].
  byteOffset + fieldSize > 8
  ifTrue:
  ["Not enough room on current eightbyte for this field, skip to next one"
  eightByteOffset := eightByteOffset + 1.
  byteOffset := 0].
  isInt
  ifTrue:
  ["If this eightbyte contains an int field, then we must use an int register"
  registerType := registerType bitOr: 1 << eightByteOffset].
  "where to put the next field?"
  byteOffset := byteOffset + fieldSize.
  byteOffset >= 8
  ifTrue:
  ["This eightbyte is full, skip to next one"
  eightByteOffset := eightByteOffset + 1.
  byteOffset := 0]]].
  ^registerType!

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 *'>
+ ^calloutState structReturnType < 2r110!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory or not."
- ^returnStructSize <= (WordSize * 2)!

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

Item was added:
+ ----- 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: true>
+
+ calloutState structReturnType: (self canReturnInRegistersStructOfSize: calloutState structReturnSize)!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>ffiReturnStruct:ofType:in: (in category 'callout support') -----
  ffiReturnStruct: intRetPtr ofType: ffiRetType in: calloutState
  <var: #intRetPtr type: #'void *'>
  <var: #calloutState type: #'CalloutState *'>
  "Create a structure return value from an external function call.  The value has been stored in
  alloca'ed space pointed to by the calloutState or in the return value passed by pointer."
  | retOop retClass oop |
  <inline: true>
  retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.
  retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.
  self remapOop: retOop
  in: [oop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: calloutState structReturnSize].
  self memcpy: (interpreterProxy firstIndexableField: oop)
+ _: ((self returnStructInRegisters: calloutState)
- _: ((self returnStructInRegisters: calloutState structReturnSize)
  ifTrue: [intRetPtr]
  ifFalse: [calloutState limit])
  _: calloutState structReturnSize.
  interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
  ^retOop!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
+ returnStructInRegisters: calloutState
+ "Return thrue register if structReturnType is true"
+ <var: #calloutState type: #'CalloutState *'>
+ ^calloutState structReturnType!
- returnStructInRegisters: returnStructSize
- "Answer if a struct result of a given size is returned in memory or not."
- ^returnStructSize <= WordSize and: ["returnStructSize isPowerOfTwo" (returnStructSize bitAnd: returnStructSize-1) = 0]!