<div dir="ltr"><div dir="ltr"><br></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">Le jeu. 30 janv. 2020 à 00:50, <<a href="mailto:commits@source.squeak.org">commits@source.squeak.org</a>> a écrit :<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"> <br>
Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2687.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2687.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-nice.2687<br>
Author: nice<br>
Time: 30 January 2020, 12:48:42.987807 am<br>
UUID: c5a0bd9f-2dd5-4f17-a014-28827e5008c2<br>
Ancestors: VMMaker.oscog-eem.2686<br>
<br>
FFI X64 SysV: check for unaligned struct and pass them in MEMORY (alloca'd memory passed thru a pointer).<br>
<br>
Note: assume that an unaligned struct can be recognized as having a different size (declared size) than the size of properly aligned struct with same fields.<br>
<br>
Note: this is WIP, and should work for packed struct passed by value, but does not yet work for returned struct, because #ffiCall:ArgArrayOrNil:NumArgs: is using #returnStructInRegisters: which only check for size, not for alignment.<br>
<br>
Use a new (branchless) formulation for aligning the byteSize to next multiple of fieldAlignment.<br>
<br>
Encode registryType of invalid unaligned candidate as 2r110, and pass the struct address returned by the foreign function in $RAX register in place of callout limit when stuct is returned by MEMORY.<br>
<br>
NEXT IDEA: currently, we recompute the registerType at each call with recursive functions which does not sound as the right thing for an efficient FFI.<br>
I plan to use some unused bits of the compiledSpec as a cache to store this registerType information (using bitXor: 2r1111, so as un-initialized cache still be 0 - that's why I have encoded INVALID as 2r110, leaving 2r111 for UNINITIALIZED). Such cache would be ABI-defined.<br>
I propose highest 4 bytes 16rF0000000.<br></blockquote><div>err, highest four bits of course...</div><div>The compiledSpec cache should be reset when restarting the image on a different OS, which is another detail to handle (compiledSpec are currently copied as a literal in the method invoking FFI primitive).</div><div><br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">
<br>
=============== Diff against VMMaker.oscog-eem.2686 ===============<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin>>alignmentOfStructSpec:OfLength:StartingAt: (in category 'marshalling-struct') -----<br>
  alignmentOfStructSpec: specs OfLength: specSize StartingAt: indexPtr<br>
        "Answer with the alignment requirement for a structure/union.<br>
        Note that indexPtr is a pointer so as to be changed on return.<br>
        On input, the index points to the structure header (the one with FFIFlagStructure + structSize).<br>
        On output, the index points the the structure trailer (the FFIFlagStructure)."<br>
        | spec byteAlignment thisAlignment |<br>
        <var: #specs type: #'unsigned int*'><br>
        <var: #indexPtr type: #'unsigned int*'><br>
        <inline: false><br>
        spec := specs at: (indexPtr at: 0).<br>
        self assert: (spec bitAnd: FFIFlagPointer + FFIFlagAtomic + FFIFlagStructure) = FFIFlagStructure.<br>
        byteAlignment := 1.<br>
        [indexPtr at: 0 put: (indexPtr at: 0) + 1.<br>
        (indexPtr at: 0) < specSize]<br>
                whileTrue:<br>
                        [spec := specs at: (indexPtr at: 0).<br>
                        spec = FFIFlagStructure<br>
                                ifTrue: [^byteAlignment].<br>
                        thisAlignment := (spec anyMask: FFIFlagPointer)<br>
                                ifTrue: [BytesPerWord]<br>
                                ifFalse: [(spec anyMask: FFIFlagStructure)<br>
                                        ifTrue: [self alignmentOfStructSpec: specs OfLength: specSize StartingAt: indexPtr]<br>
                                        ifFalse: [spec bitAnd: FFIStructSizeMask]].<br>
                        byteAlignment := byteAlignment max: thisAlignment].<br>
+       self assert: false. "should not reach here - because only ever called for sub-struct"<br>
+       ^byteAlignment!<br>
-       self assert: false. "should not reach here"<br>
-       ^-1!<br>
<br>
Item was added:<br>
+ ----- Method: ThreadedFFIPlugin>>checkAlignmentOfStructSpec:OfLength:StartingAt: (in category 'marshalling-struct') -----<br>
+ checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: startIndex<br>
+       "Check the alignment of a structure and return true if correctly aligned.<br>
+       If computed size = declared size, then the struct is assumed correctly aligned."<br>
+       | index spec computedSize fieldAlignment fieldSize declaredSize maxAlignment |<br>
+       <var: #specs type: #'unsigned int*'><br>
+       <var: #indexPtr type: #'unsigned int*'><br>
+       <inline: false><br>
+       index := startIndex.<br>
+       spec := specs at: index.<br>
+       self assert: (spec bitAnd: FFIFlagPointer + FFIFlagAtomic + FFIFlagStructure) = FFIFlagStructure.<br>
+       (self isUnionSpec: specs OfLength: specSize StartingAt: index) ifTrue: [^true].<br>
+       declaredSize := spec bitAnd: FFIStructSizeMask.<br>
+       computedSize := 0.<br>
+       maxAlignment := 1.<br>
+       [index := index + 1.<br>
+       index < specSize]<br>
+               whileTrue:<br>
+                       [spec := specs at: index.<br>
+                       spec = FFIFlagStructure<br>
+                               ifTrue: [^(computedSize - 1 bitOr: maxAlignment - 1) + 1 = declaredSize].<br>
+                       (spec anyMask: FFIFlagPointer)<br>
+                               ifTrue:<br>
+                                       [fieldSize := BytesPerWord.<br>
+                                       fieldAlignment := fieldSize]<br>
+                               ifFalse:<br>
+                                       [fieldSize := spec bitAnd: FFIStructSizeMask.<br>
+                                       (spec anyMask: FFIFlagStructure)<br>
+                                               ifTrue:<br>
+                                                       [(self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)<br>
+                                                               ifFalse: [^false].<br>
+                                                        fieldAlignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: index)]<br>
+                                               ifFalse: [fieldAlignment := fieldSize]].<br>
+                       "round to fieldAlignment"<br>
+                       maxAlignment := maxAlignment max: fieldAlignment.<br>
+                       computedSize := (computedSize - 1 bitOr: fieldAlignment - 1) + 1.<br>
+                       computedSize := computedSize + fieldSize].<br>
+       ^(computedSize - 1 bitOr: maxAlignment - 1) + 1 = declaredSize!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin>>isUnionSpec:OfLength:StartingAt: (in category 'marshalling-struct') -----<br>
  isUnionSpec: specs OfLength: specSize StartingAt: startIndex<br>
        "We can't easily distinguish union from structures with available flags.<br>
        But we have a trick: a union should have one field size equal to its own size."<br>
        | index spec unionSize thisSize |<br>
        <var: #specs type: #'unsigned int*'><br>
+       <inline: false><br>
        index := startIndex.<br>
        spec := specs at: index.<br>
        self assert: (spec bitAnd: FFIFlagPointer + FFIFlagAtomic + FFIFlagStructure) = FFIFlagStructure.<br>
        unionSize := spec bitAnd: FFIStructSizeMask.<br>
        [index := index + 1.<br>
        index < specSize]<br>
                whileTrue:<br>
                        [spec := specs at: index.<br>
                        spec = FFIFlagStructure<br>
                                ifTrue: [^false].<br>
                        thisSize := spec bitAnd: FFIStructSizeMask.<br>
                        thisSize = unionSize ifTrue: [^true].<br>
                        ((spec bitAnd: FFIFlagPointer + FFIFlagStructure) = FFIFlagStructure)<br>
                                ifTrue:<br>
                                        ["Asking for alignment is a trick for skipping this sub structure/union"<br>
                                        self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: index)]].<br>
-       self assert: false. "should not reach here"<br>
        ^false!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedX64SysVFFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----<br>
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState<br>
        <var: #procAddr type: #'void *'><br>
        <var: #calloutState type: #'CalloutState *'><br>
        <var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double, double, double, double, double)'><br>
        "Go out, call this guy and create the return value.  This *must* be inlined because of<br>
         the alloca of the outgoing stack frame in ffiCall:WithFlags:NumArgs:Args:AndTypes:"<br>
        | myThreadIndex atomicType floatRet intRet sddRet sdiRet sidRet siiRet returnStructByValue registerType sRetPtr |<br>
        <var: #floatRet type: #double><br>
        <var: #intRet type: #sqInt><br>
        <var: #siiRet type: #SixteenByteReturnII><br>
        <var: #sidRet type: #SixteenByteReturnID><br>
        <var: #sdiRet type: #SixteenByteReturnDI><br>
        <var: #sddRet type: #SixteenByteReturnDD><br>
        <var: #sRetPtr type: #'void *'><br>
        <inline: true><br>
<br>
        returnStructByValue := (calloutState ffiRetHeader bitAnd: FFIFlagStructure + FFIFlagPointer + FFIFlagAtomic) = FFIFlagStructure.<br>
        returnStructByValue<br>
                ifTrue:<br>
                        [(self returnStructInRegisters: calloutState structReturnSize)<br>
                                ifTrue: [registerType := self registerTypeForStructSpecs: (interpreterProxy firstIndexableField: calloutState ffiRetSpec) OfLength: (interpreterProxy slotSizeOf: calloutState ffiRetSpec)]<br>
+                               ifFalse: [registerType := 2r110 "cannot pass by register"]].<br>
-                               ifFalse: [registerType := 2r101 "encodes a single sqInt"]].<br>
<br>
        myThreadIndex := interpreterProxy disownVM: (self disownFlagsFor: calloutState).<br>
<br>
        calloutState floatRegisterIndex > 0 ifTrue:<br>
                [self <br>
                        load: (calloutState floatRegisters at: 0)<br>
                        Flo: (calloutState floatRegisters at: 1)<br>
                        a: (calloutState floatRegisters at: 2)<br>
                        t: (calloutState floatRegisters at: 3)<br>
                        R: (calloutState floatRegisters at: 4)<br>
                        e: (calloutState floatRegisters at: 5)<br>
                        g: (calloutState floatRegisters at: 6)<br>
                        s: (calloutState floatRegisters at: 7)].<br>
<br>
        (self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:<br>
                [self setsp: calloutState argVector].<br>
<br>
        atomicType := self atomicTypeOf: calloutState ffiRetHeader.<br>
        (atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:<br>
                [atomicType = FFITypeSingleFloat<br>
                        ifTrue:<br>
                                [floatRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5)]<br>
                        ifFalse: "atomicType = FFITypeDoubleFloat"<br>
                                [floatRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5)].<br>
<br>
                 interpreterProxy ownVM: myThreadIndex.<br>
<br>
                 ^interpreterProxy floatObjectOf: floatRet].<br>
<br>
        returnStructByValue  ifFalse:<br>
                [intRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                interpreterProxy ownVM: myThreadIndex.<br>
                (calloutState ffiRetHeader anyMask: FFIFlagPointer) ifTrue:<br>
                        [^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].<br>
                ^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState].<br>
<br>
        registerType<br>
                caseOf:<br>
                        {[2r00] -><br>
                                [sddRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnDD (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                                sRetPtr := (self addressOf: sddRet) asVoidPointer].<br>
                         [2r01] -><br>
                                [sidRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnID (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                                sRetPtr := (self addressOf: sidRet) asVoidPointer].<br>
                         [2r10] -><br>
                                [sdiRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnDI (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                                sRetPtr := (self addressOf: sdiRet) asVoidPointer].<br>
                         [2r11] -><br>
                                [siiRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturnII (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                                sRetPtr := (self addressOf: siiRet) asVoidPointer].<br>
                         [2r100] -><br>
                                [floatRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
                                sRetPtr := (self addressOf: floatRet) asVoidPointer].<br>
                         [2r101] -><br>
                                [intRet := self <br>
                                        dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') <br>
                                        with: (calloutState integerRegisters at: 0)<br>
                                        with: (calloutState integerRegisters at: 1)<br>
                                        with: (calloutState integerRegisters at: 2)<br>
                                        with: (calloutState integerRegisters at: 3)<br>
                                        with: (calloutState integerRegisters at: 4)<br>
                                        with: (calloutState integerRegisters at: 5).<br>
+                               sRetPtr := (self addressOf: intRet) asVoidPointer].<br>
+                        [2r110] -><br>
+                               ["return a pointer to alloca'd memory"<br>
+                               intRet := self <br>
+                                       dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'sqInt (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')<br>
+                                       with: (calloutState integerRegisters at: 0)<br>
+                                       with: (calloutState integerRegisters at: 1)<br>
+                                       with: (calloutState integerRegisters at: 2)<br>
+                                       with: (calloutState integerRegisters at: 3)<br>
+                                       with: (calloutState integerRegisters at: 4)<br>
+                                       with: (calloutState integerRegisters at: 5).<br>
+                               sRetPtr := intRet asVoidPointer "address of struct is returned in RAX, which also is calloutState limit"]}<br>
-                               sRetPtr := (self addressOf: intRet) asVoidPointer]}<br>
                otherwise:<br>
                        [interpreterProxy ownVM: myThreadIndex.<br>
                        self ffiFail: FFIErrorWrongType. ^nil].<br>
<br>
        interpreterProxy ownVM: myThreadIndex.<br>
        ^self ffiReturnStruct: sRetPtr ofType: (self ffiReturnType: specOnStack) in: calloutState!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedX64SysVFFIPlugin>>ffiPushStructure:ofSize:typeSpec:ofLength:in: (in category 'marshalling') -----<br>
  ffiPushStructure: pointer ofSize: structSize typeSpec: argSpec ofLength: argSpecSize in: calloutState<br>
        <var: #pointer type: #'void *'><br>
        <var: #argSpec type: #'sqInt *'><br>
        <var: #calloutState type: #'CalloutState *'><br>
        <inline: true><br>
        | roundedSize registerType numDoubleRegisters numIntegerRegisters passField0InXmmReg passField1InXmmReg |<br>
        structSize <= 16 ifTrue:<br>
                ["See sec 3.2.3 of <a href="http://people.freebsd.org/~obrien/amd64-elf-abi.pdf" rel="noreferrer" target="_blank">http://people.freebsd.org/~obrien/amd64-elf-abi.pdf</a>. (dravft version 0.90).<br>
                  All of the folowing are passed in registers:<br>
                        typedef struct { long a; } s0;<br>
                        typedef struct { double a; } s1;<br>
                        typedef struct { long a; double b; } s2;<br>
                        typedef struct { int a; int b; double c; } s2a;<br>
                        typedef struct { short a; short b; short c; short d; double e; } s2b;<br>
                        typedef struct { long a; float b; } s2f;<br>
                        typedef struct { long a; float b; float c; } s2g;<br>
                        typedef struct { int a; float b; int c; float d; } s2h;"<br>
                 registerType := self registerTypeForStructSpecs: (self cCoerce: argSpec to: #'unsigned int *') OfLength: argSpecSize.<br>
+                registerType = 2r110 "check case of invalid alignment => pass by memory"<br>
+                       ifFalse: <br>
+                                [passField0InXmmReg := (registerType bitAnd: 1) = 0.<br>
+                                 structSize <= 8<br>
+                                       ifTrue:<br>
+                                               [numIntegerRegisters := registerType bitAnd: 1.<br>
+                                                numDoubleRegisters := 1 - numIntegerRegisters]<br>
+                                       ifFalse:<br>
+                                               [passField1InXmmReg := (registerType bitAnd: 2) = 0.<br>
+                                                numIntegerRegisters := (registerType bitAnd: 2) >> 1 + (registerType bitAnd: 1).<br>
+                                                numDoubleRegisters := 2 - numIntegerRegisters].<br>
+                                (calloutState floatRegisterIndex + numDoubleRegisters <= NumFloatRegArgs<br>
+                                 and: [calloutState integerRegisterIndex + numIntegerRegisters <= NumIntRegArgs]) ifTrue:<br>
+                                       [passField0InXmmReg<br>
+                                               ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 0) in: calloutState]<br>
+                                               ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 0) in: calloutState].<br>
+                                        structSize > 8 ifTrue:<br>
+                                               [passField1InXmmReg<br>
+                                                       ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 1) in: calloutState]<br>
+                                                       ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 1) in: calloutState]].<br>
+                                        ^0]]].<br>
-                passField0InXmmReg := (registerType bitAnd: 1) = 0.<br>
-                structSize <= 8<br>
-                       ifTrue:<br>
-                               [numIntegerRegisters := registerType bitAnd: 1.<br>
-                                numDoubleRegisters := 1 - numIntegerRegisters]<br>
-                       ifFalse:<br>
-                               [passField1InXmmReg := (registerType bitAnd: 2) = 0.<br>
-                                numIntegerRegisters := (registerType bitAnd: 2) >> 1 + (registerType bitAnd: 1).<br>
-                                numDoubleRegisters := 2 - numIntegerRegisters].<br>
-               (calloutState floatRegisterIndex + numDoubleRegisters <= NumFloatRegArgs<br>
-                 and: [calloutState integerRegisterIndex + numIntegerRegisters <= NumIntRegArgs]) ifTrue:<br>
-                       [passField0InXmmReg<br>
-                               ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 0) in: calloutState]<br>
-                               ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 0) in: calloutState].<br>
-                        structSize > 8 ifTrue:<br>
-                               [passField1InXmmReg<br>
-                                       ifTrue: [self ffiPushDoubleFloat: ((self cCoerceSimple: pointer to: #'double *') at: 1) in: calloutState]<br>
-                                       ifFalse: [self ffiPushSignedLongLong: ((self cCoerceSimple: pointer to: #'long long *') at: 1) in: calloutState]].<br>
-                        ^0]].<br>
<br>
        roundedSize := structSize + 7 bitClear: 7.<br>
        calloutState currentArg + roundedSize > calloutState limit ifTrue:<br>
                 [^FFIErrorCallFrameTooBig].<br>
        self memcpy: calloutState currentArg _: (self cCoerceSimple: pointer to: 'char *') _: structSize.<br>
        calloutState currentArg: calloutState currentArg + roundedSize.<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedX64SysVFFIPlugin>>ffiReturnStruct:ofType:in: (in category 'callout support') -----<br>
+ ffiReturnStruct: structRetPtr ofType: ffiRetType in: calloutState<br>
+       <var: #structRetPtr type: #'void *'><br>
- ffiReturnStruct: sixteenByteRetPtr ofType: ffiRetType in: calloutState<br>
-       <var: #sixteenByteRetPtr type: #'void *'><br>
        <var: #calloutState type: #'CalloutState *'><br>
        "Create a structure return value from an external function call.  The value has been stored in<br>
         alloca'ed space pointed to by the calloutState or in the return value passed by pointer."<br>
        | retOop retClass oop |<br>
        <inline: true><br>
        retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.<br>
        retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.<br>
        self remapOop: retOop<br>
                in: [oop := interpreterProxy <br>
                                        instantiateClass: interpreterProxy classByteArray <br>
                                        indexableSize: calloutState structReturnSize].<br>
        self memcpy: (interpreterProxy firstIndexableField: oop)<br>
+                _: structRetPtr<br>
-               _: ((self returnStructInRegisters: calloutState structReturnSize)<br>
-                               ifTrue: [sixteenByteRetPtr]<br>
-                               ifFalse: [calloutState limit])<br>
                 _: calloutState structReturnSize.<br>
        interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.<br>
        ^retOop!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedX64SysVFFIPlugin>>registerTypeForStructSpecs:OfLength: (in category 'marshalling') -----<br>
  registerTypeForStructSpecs: specs OfLength: specSize<br>
        "Answer with a number characterizing the register type for passing a struct of size <= 16 bytes.<br>
        The bit at offset i of registerType is set to 1 if eightbyte at offset i is a int register (RAX ...)<br>
        The bit at offset 2 indicates if there is a single eightbyte (struct size <= 8)<br>
        * 2r00 for float float (XMM0 XMM1)<br>
        * 2r01 for int float (RAX XMM0)<br>
        * 2r10 for float int (XMM0 RAX)<br>
        * 2r11 for int int (RAX RDX)<br>
        * 2r100 for float (XMM0)<br>
        * 2r101 for int (RAX)<br>
+       * 2r110 INVALID (not aligned)<br>
        Beware, the bits must be read from right to left for decoding register type.<br>
        Note: this method reconstructs the struct layout according to X64 alignment rules.<br>
        Therefore, it will not work for packed struct or other exotic alignment."<br>
<br>
        <var: #specs type: #'unsigned int*'><br>
        <var: #subIndex type: #'unsigned int'><br>
        | eightByteOffset byteOffset index registerType spec fieldSize alignment atomic subIndex isInt |<br>
+       index := 0.<br>
+       (self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)<br>
+               ifFalse: [^2r110].<br>
        eightByteOffset := 0.<br>
        byteOffset := 0.<br>
-       index := 0.<br>
        registerType := ((specs at: index) bitAnd: FFIStructSizeMask) <= 8 ifTrue: [2r100] ifFalse: [0].<br>
        [(index := index + 1) < specSize]<br>
                whileTrue:<br>
                        [spec := specs at: index.<br>
                        isInt := false.<br>
                        spec = FFIFlagStructure "this marks end of structure and should be ignored"<br>
                                ifFalse:<br>
                                        [(spec anyMask: FFIFlagPointer)<br>
                                                ifTrue:<br>
                                                        [fieldSize := BytesPerWord.<br>
                                                        alignment := fieldSize.<br>
                                                        isInt := true]<br>
                                                ifFalse:<br>
                                                        [(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)<br>
                                                                caseOf:<br>
                                                                        {[FFIFlagStructure] -><br>
                                                                                [fieldSize := 0.<br>
                                                                                subIndex := index.<br>
                                                                                alignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: subIndex)].<br>
                                                                        [FFIFlagAtomic] -><br>
                                                                                [fieldSize := spec bitAnd: FFIStructSizeMask.<br>
                                                                                alignment := fieldSize.<br>
                                                                                atomic := self atomicTypeOf: spec.<br>
                                                                                isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}<br>
                                                                otherwise: ["invalid spec" ^-1]].<br>
                                        (byteOffset bitAnd: alignment - 1) = 0<br>
                                                ifFalse:<br>
                                                        ["this field requires alignment"<br>
                                                        byteOffset := (byteOffset bitClear: alignment - 1) + alignment].<br>
                                        byteOffset + fieldSize > 8<br>
                                                ifTrue:<br>
                                                        ["Not enough room on current eightbyte for this field, skip to next one"<br>
                                                        eightByteOffset := eightByteOffset + 1.<br>
                                                        byteOffset := 0].<br>
                                        isInt<br>
                                                ifTrue:<br>
                                                        ["If this eightbyte contains an int field, then we must use an int register"<br>
                                                        registerType := registerType bitOr: 1 << eightByteOffset].<br>
                                        "where to put the next field?"<br>
                                        byteOffset := byteOffset + fieldSize.<br>
                                        byteOffset >= 8<br>
                                                ifTrue:<br>
                                                        ["This eightbyte is full, skip to next one"<br>
                                                        eightByteOffset := eightByteOffset + 1.<br>
                                                        byteOffset := 0]]].<br>
        ^registerType!<br>
<br>
</blockquote></div></div>