[Vm-dev] VM Maker: VMMaker.oscog-nice.1980.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Tue Nov 8 21:15:59 UTC 2016


Original commit message at:
http://smalltalkhub.com/?_escaped_fragment_=/~nice/
NiceVMExperiments/commits#!/~nice/NiceVMExperiments/commits

VMMaker.oscogLLP64-nice.1924

Work on the X64-WIN64 ABI references: msdn X64 return values
https://msdn.microsoft.com/en-us/library/7572ztz4.aspx msdn X64 parameter
passing https://msdn.microsoft.com/en-us/library/zthk2dkh.aspx

There are only 4 params passed by register, whatever int (or pointer) or
float So we cannot distinguish float register index and integer resgister
index.

Correct parameter passing of struct: - 8 bytes max are allowed for passing
by value not 16 - pass a copy of contents, not of pointer

Correct return value of struct: don't forget that the byte length must be a
power of two for returning by register

Correct (fake) passing of float registers: there are only 4 registers at
most, not 5.


2016-11-06 9:41 GMT+01:00 <commits at source.squeak.org>:

>
> Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1980.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-nice.1980
> Author: nice
> Time: 6 November 2016, 9:39:52.658038 am
> UUID: eeec5e65-ce2b-4698-930d-209077139d02
> Ancestors: VMMaker.oscog-nice.1979
>
> Fix shifting in ffiCreateIntegralResultOop:ofAtomicType:in: like already
> applied in primitiveFFIIntegerAt/Put
>
> Properly count the parameters passed by register for X64 Win64: there are
> only 4 of them, either floating point or integer or any mix, but not 4
> floating point and 4 integers.
>
> Fix passing structure by value in X64 Win64: size must be a power of 2,
> and it's not possible to pass a 16bytes structure into two registers.
>
> =============== Diff against VMMaker.oscog-nice.1979 ===============
>
> Item was removed:
> - ----- Method: ThreadedFFICalloutStateForX64>>floatRegisterIndex: (in
> category 'accessing') -----
> - floatRegisterIndex: anObject
> -
> -       ^floatRegisterIndex := anObject!
>
> Item was removed:
> - ----- Method: ThreadedFFICalloutStateForX64>>floatRegisters: (in
> category 'accessing') -----
> - floatRegisters: anObject
> -
> -       ^floatRegisters := anObject!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64>>incrementFloatRegisterIndex
> (in category 'accessing') -----
> + incrementFloatRegisterIndex
> +       ^floatRegisterIndex := floatRegisterIndex + 1!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64>>incrementIntegerRegisterIndex
> (in category 'accessing') -----
> + incrementIntegerRegisterIndex
> +       ^integerRegisterIndex := integerRegisterIndex + 1!
>
> Item was removed:
> - ----- Method: ThreadedFFICalloutStateForX64>>integerRegisterIndex: (in
> category 'accessing') -----
> - integerRegisterIndex: anObject
> -
> -       ^integerRegisterIndex := anObject!
>
> Item was removed:
> - ----- Method: ThreadedFFICalloutStateForX64>>integerRegisters: (in
> category 'accessing') -----
> - integerRegisters: anObject
> -
> -       ^integerRegisters := anObject!
>
> Item was changed:
>   ThreadedFFICalloutStateForX64 subclass: #ThreadedFFICalloutStateForX64W
> in64
> +       instanceVariableNames: 'floatRegisterSignature'
> -       instanceVariableNames: ''
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'VMMaker-Plugins-FFI'!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64Win64 class>>
> instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
> + instVarNamesAndTypesForTranslationDo: aBinaryBlock
> +       "enumerate aBinaryBlock with the names and C type strings for the
> inst vars to include in a ThreadedFFICalloutState struct."
> +
> +       ThreadedFFICalloutStateForX64 instVarNamesAndTypesForTranslationDo:
> aBinaryBlock.
> +       ThreadedFFICalloutStateForX64Win64 instVarNames do:
> +               [:ivn|
> +               aBinaryBlock
> +                       value: ivn
> +                       value: (ivn caseOf: {
> +
>  ['floatRegisterSignature']      -> [#int] }
> +                                       otherwise:
> +                                               [#sqInt])]!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64Win64>>floatRegisterSignature
> (in category 'accessing') -----
> + floatRegisterSignature
> +       ^floatRegisterSignature!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64Win64>>incrementFloatRegisterIndex
> (in category 'accessing') -----
> + incrementFloatRegisterIndex
> +       "There are only 4 args passed by register int or float.
> +       So we can't distinguish the float index from the integer index.
> +       So we have to increment both.
> +
> +       Consequently, floatRegisterIndex cannot be used anymore to detect
> presence of float parameter.
> +       However, we set a signature bitmap indicating which register
> position is used to pass a float.
> +
> +       IMPLEMENTATION NOTES:
> +       There are code generator hacks that bypass the accessors.
> +       So we cannot just redefine the method floatRegisterIndex as
> ^integerRegisterIndex.
> +       Instead we must maintain the two indices"
> +
> +       floatRegisterSignature := floatRegisterSignature + (1 <<
> floatRegisterIndex).
> +       ^integerRegisterIndex := floatRegisterIndex := floatRegisterIndex
> + 1!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64Win64>>incrementIntegerRegisterIndex
> (in category 'accessing') -----
> + incrementIntegerRegisterIndex
> +       "There are only 4 args passed by register int or float.
> +       So we can't distinguish the float index from the integer index.
> +       So we have to increment both.
> +
> +       IMPLEMENTATION NOTES:
> +       There are code generator hacks that bypass the accessors.
> +       So we cannot just redefine the method floatRegisterIndex as
> ^integerRegisterIndex.
> +       Instead we must maintain the two indices"
> +
> +       ^floatRegisterIndex := integerRegisterIndex :=
> integerRegisterIndex + 1!
>
> Item was added:
> + ----- Method: ThreadedFFICalloutStateForX64Win64>>initialize (in
> category 'initialize-release') -----
> + initialize
> +       super initialize.
> +       floatRegisterSignature := 0.!
>
> Item was changed:
>   ----- Method: ThreadedFFIPlugin>>ffiCreateIntegralResultOop:ofAtomicType:in:
> (in category 'callout support') -----
>   ffiCreateIntegralResultOop: retVal ofAtomicType: atomicType in:
> calloutState
>         <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].
> -                                       ifFalse:[retVal bitAnd: 1 <<
> (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).
> -                       value := retVal bitAnd: (1 asUnsignedLong << shift
> - 1).
>                         (atomicType anyMask: 1) ifTrue:
>                                 ["make the guy signed"
> +                               mask := 1 asUnsignedLongLong << (shift-1).
> -                               mask := 1 asUnsignedLong << (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]]
>                 ifFalse:
>                         [interpreterProxy characterObjectOf: (retVal
> bitAnd: 16rFF)]!
>
> Item was changed:
>   ----- Method: ThreadedX64FFIPlugin>>ffiPushDoubleFloat:in: (in category
> 'marshalling') -----
>   ffiPushDoubleFloat: value in: calloutState
>         <var: #value type: #double>
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>
>         calloutState floatRegisterIndex < NumFloatRegArgs
>                 ifTrue:
>                         [calloutState floatRegisters at: calloutState
> floatRegisterIndex put: value.
> +                        calloutState incrementFloatRegisterIndex]
> -                        calloutState floatRegisterIndex: calloutState
> floatRegisterIndex + 1]
>                 ifFalse:
>                         [calloutState currentArg + WordSize > calloutState
> limit ifTrue:
>                                 [^FFIErrorCallFrameTooBig].
>                          interpreterProxy storeFloatAtPointer:
> calloutState currentArg from: value.
>                          calloutState currentArg: calloutState currentArg
> + WordSize].
>         ^0!
>
> Item was changed:
>   ----- Method: ThreadedX64FFIPlugin>>ffiPushPointer:in: (in category
> 'marshalling') -----
>   ffiPushPointer: pointer in: calloutState
>         <var: #pointer type: #'void *'>
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: pointer asInteger.
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'signed char').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'signed char').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: value.
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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>>ffiPushSignedLongLong:in: (in
> category 'marshalling') -----
>   ffiPushSignedLongLong: value in: calloutState
>         <var: #value type: #sqLong>
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #usqInt).
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'signed short').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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>>ffiPushSingleFloat:in: (in category
> 'marshalling') -----
>   ffiPushSingleFloat: value in: calloutState
>         <var: #value type: #float>
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>
>         calloutState floatRegisterIndex < NumFloatRegArgs
>                 ifTrue:
>                         [(self cCoerce: calloutState floatRegisters +
> calloutState floatRegisterIndex to: #'float *') at: 0 put: value.
> +                        calloutState incrementFloatRegisterIndex]
> -                        calloutState floatRegisterIndex: calloutState
> floatRegisterIndex + 1]
>                 ifFalse:
>                         [calloutState currentArg + WordSize > calloutState
> limit ifTrue:
>                                 [^FFIErrorCallFrameTooBig].
>                          interpreterProxy storeFloatAtPointer:
> calloutState currentArg from: value.
>                          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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned char').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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>>ffiPushUnsignedChar:in: (in
> category 'marshalling') -----
>   ffiPushUnsignedChar: value in: calloutState
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned char').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: value.
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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>>ffiPushUnsignedLongLong:in: (in
> category 'marshalling') -----
>   ffiPushUnsignedLongLong: value in: calloutState
>         <var: #value type: #usqLong>
>         <var: #calloutState type: #'CalloutState *'>
>         <inline: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: value.
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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: true>
>         calloutState integerRegisterIndex < NumIntRegArgs
>                 ifTrue:
>                         [calloutState integerRegisters at: calloutState
> integerRegisterIndex put: (self cCoerceSimple: value to: #'unsigned short').
> +                        calloutState incrementIntegerRegisterIndex]
> -                        calloutState integerRegisterIndex: calloutState
> integerRegisterIndex + 1]
>                 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:
>   ThreadedX64FFIPlugin subclass: #ThreadedX64Win64FFIPlugin
>         instanceVariableNames: ''
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'VMMaker-Plugins-FFI'!
>
> + !ThreadedX64Win64FFIPlugin commentStamp: 'nice 8/10/2016 19:23' prior: 0!
> + This subclass is for the Win64 x86-64 ABI.  The Win64 ABI uses 4 integer
> registers or 4 double-precision floating-point registers or a mix of the
> two.  See w.g. https://msdn.microsoft.com/en-us/library/ms235286.aspx, or
> google for "Overview of x64 Calling Conventions - MSDN - Microsoft".
> - !ThreadedX64Win64FFIPlugin commentStamp: 'eem 2/16/2016 19:39' prior: 0!
> - This subclass is for the Win64 x86-64 ABI.  The System V ABI uses 4
> integer registers and 4 double-precision floating-point registers.  See
> w.g. https://msdn.microsoft.com/en-us/library/ms235286.aspx, or google
> for "Overview of x64 Calling Conventions - MSDN - Microsoft".
>
>   Note that unlike the System V x86-64 ABI, the Win64 ABI does /not/
> decompose structs passed by value across available parameter registers.!
>
> Item was added:
> + ----- Method: ThreadedX64Win64FFIPlugin class>>calloutStateClass (in
> category 'translation') -----
> + calloutStateClass
> +       ^ThreadedFFICalloutStateForX64Win64!
>
> Item was changed:
>   ----- Method: ThreadedX64Win64FFIPlugin>>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)'>
>         "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 loadFloatRegs oop |
>         <var: #floatRet type: #double>
>         <var: #intRet type: #usqLong>
>         <inline: true>
>         self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs
> class].
>         self cppIf: COGMTVM ifTrue:
>         [(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
>                 [myThreadIndex := interpreterProxy disownVM: 0]].
>
>         self registerArgsSlop + self cStackAlignment > 0 ifTrue:
>                 [self setsp: calloutState argVector].
>
> +       calloutState floatRegisterSignature > 0 ifTrue:
> -       calloutState floatRegisterIndex > 0 ifTrue:
>                 [self
>                         load: (calloutState floatRegisters at: 0)
>                         Flo: (calloutState floatRegisters at: 1)
>                         at: (calloutState floatRegisters at: 2)
>                         Re: (calloutState floatRegisters at: 3)
>                         gs: (calloutState floatRegisters at: 4)].
>
>         atomicType := self atomicTypeOf: calloutState ffiRetHeader.
>         (atomicType >> 1) = (FFITypeSingleFloat >> 1)
>                 ifTrue:
>                         [atomicType = FFITypeSingleFloat
>                                 ifTrue:
>                                         [floatRet := self
>                                                 dispatchFunctionPointer:
> (self cCoerceSimple: procAddr to: 'float (*)(long, long, long, long)')
>                                                 with: (calloutState
> integerRegisters at: 0)
>                                                 with: (calloutState
> integerRegisters at: 1)
>                                                 with: (calloutState
> integerRegisters at: 2)
>                                                 with: (calloutState
> integerRegisters at: 3)]
>                                 ifFalse: "atomicType = FFITypeDoubleFloat"
>                                         [floatRet := self
>                                                 dispatchFunctionPointer:
> (self cCoerceSimple: procAddr to: 'double (*)(long, long, long, long)')
>                                                 with: (calloutState
> integerRegisters at: 0)
>                                                 with: (calloutState
> integerRegisters at: 1)
>                                                 with: (calloutState
> integerRegisters at: 2)
>                                                 with: (calloutState
> integerRegisters at: 3)]]
>                 ifFalse:
>                         [intRet := self
>                                 dispatchFunctionPointer: (self
> cCoerceSimple: procAddr to: 'usqLong (*)(long, long, long, long)')
>                                 with: (calloutState integerRegisters at: 0)
>                                 with: (calloutState integerRegisters at: 1)
>                                 with: (calloutState integerRegisters at: 2)
>                                 with: (calloutState integerRegisters at:
> 3)].
>         "undo any callee argument pops because it may confuse stack
> management with the alloca."
>         (self isCalleePopsConvention: calloutState callFlags) ifTrue:
>                 [self setsp: calloutState argVector].
>
>         self cppIf: COGMTVM ifTrue:
>         [(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
>                 [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:
>                                 [oop := self ffiReturnPointer: intRet
> ofType: (self ffiReturnType: specOnStack) in: calloutState]
>                         ifFalse:
>                                 [oop := self ffiReturnStruct: intRet
> ofType: (self ffiReturnType: specOnStack) in: calloutState].
>                  ^oop].
>
>         (atomicType >> 1) = (FFITypeSingleFloat >> 1)
>                 ifTrue:
>                         [oop := interpreterProxy floatObjectOf: floatRet]
>                 ifFalse:
>                         [oop := self ffiCreateIntegralResultOop: intRet
>                                                 ofAtomicType: atomicType
>                                                 in: calloutState].
>         ^interpreterProxy methodReturnValue: oop!
>
> 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: true>
>         structSize <= 0 ifTrue:
>                 [^FFIErrorStructSize].
> +       (structSize <= WordSize
> -       (structSize <= 16
>          and: [(structSize bitAnd: structSize - 1) = 0 "a.k.a. structSize
> isPowerOfTwo"]) ifTrue:
> +               [| arg |
> +               self mem: (self addressOf: arg) cp: pointer y: structSize.
> +               ^self ffiPushUnsignedLongLong: arg in: calloutState].
> -               [^self ffiPushUnsignedLongLong: (self cCoerceSimple:
> pointer to: #usqLong) in: calloutState].
>
>         "For now just push the pointer; we should copy the struct to the
> outgoing stack frame!!!!"
>         self flag: 'quick hack'.
>         ^self ffiPushPointer: pointer in: calloutState!
>
> Item was changed:
>   ----- Method: ThreadedX64Win64FFIPlugin>>returnStructInRegisters: (in
> category 'marshalling') -----
>   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]!
> -       ^returnStructSize <= WordSize!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20161108/0d163e3b/attachment-0001.html>


More information about the Vm-dev mailing list