Skip to content
This repository has been archived by the owner on Jan 5, 2023. It is now read-only.

Commit

Permalink
Implementing marshalling
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Nov 3, 2020
1 parent e62944b commit 96acc74
Show file tree
Hide file tree
Showing 12 changed files with 134 additions and 9 deletions.
2 changes: 1 addition & 1 deletion src/ThreadedFFI-UFFI-Tests/TFUFFITestCase.class.st
Expand Up @@ -17,7 +17,7 @@ TFUFFITestCase class >> isAbstract [
TFUFFITestCase class >> testParameters [

^ ParametrizedTestMatrix new
forSelector: #ffiLibrary addOptions: { TFTestLibraryUsingWorker. TFTestLibraryUsingSameThreadRunner. }
forSelector: #ffiLibrary addOptions: { TFTestLibraryUsingSameThreadRunner. TFTestLibraryUsingWorker. }
]

{ #category : #accessing }
Expand Down
6 changes: 6 additions & 0 deletions src/ThreadedFFI-UFFI/ExternalAddress.extension.st
@@ -0,0 +1,6 @@
Extension { #name : #ExternalAddress }

{ #category : #'*ThreadedFFI-UFFI' }
ExternalAddress >> thunk [
^ self
]
2 changes: 1 addition & 1 deletion src/ThreadedFFI-UFFI/FFILibrary.extension.st
Expand Up @@ -9,5 +9,5 @@ FFILibrary >> callbackRunningStrategy [
{ #category : #'*ThreadedFFI-UFFI' }
FFILibrary >> runner [

^ TFWorker default
^ TFSameThreadRunner uniqueInstance
]
9 changes: 7 additions & 2 deletions src/ThreadedFFI-UFFI/TFCalloutMethodBuilder.class.st
Expand Up @@ -19,7 +19,7 @@ TFCalloutMethodBuilder >> createFFICalloutLiteralFromSpec: functionSpec [

{ #category : #private }
TFCalloutMethodBuilder >> generateFFICallout: builder spec: functionSpec [
| properties |
| properties ffiLibrary |

"Copy the properties of the old method"

Expand All @@ -40,8 +40,13 @@ TFCalloutMethodBuilder >> generateFFICallout: builder spec: functionSpec [
send: #trace: ].

"Obtain the library to use"
ffiLibrary := library ifNil: [sender receiver ffiLibrary].
ffiLibrary := ffiLibrary isClass
ifFalse: [ ffiLibrary asFFILibrary ]
ifTrue: [ ffiLibrary uniqueInstance ].

builder
pushLiteral: (sender receiver ffiLibrary uniqueInstance runner).
pushLiteral: (ffiLibrary uniqueInstance runner).

"save ffi call as literal"
builder pushLiteral: (self createFFICalloutLiteralFromSpec: functionSpec).
Expand Down
9 changes: 9 additions & 0 deletions src/ThreadedFFI/ByteString.extension.st
@@ -0,0 +1,9 @@
Extension { #name : #ByteString }

{ #category : #'*ThreadedFFI' }
ByteString >> tfPointerAddress [

self pinInMemory.
^ PointerUtils oopForObject: self

]
14 changes: 14 additions & 0 deletions src/ThreadedFFI/TFBasicType.class.st
Expand Up @@ -323,6 +323,20 @@ TFBasicType >> isVoid [
^ typeName = #void
]

{ #category : #marshalling }
TFBasicType >> marshallFromPrimitive: aValue [

^ aValue

]

{ #category : #marshalling }
TFBasicType >> marshallToPrimitive: aValue [

^ aValue

]

{ #category : #primitives }
TFBasicType >> primFillType [
<primitive: 'primitiveFillBasicType'>
Expand Down
20 changes: 20 additions & 0 deletions src/ThreadedFFI/TFCallback.class.st
Expand Up @@ -77,6 +77,26 @@ TFCallback >> initialize [
parameterHandlers := #()
]

{ #category : #invoking }
TFCallback >> invokeAsFunctionWithArguments: aCollection [

| definition function preparedArguments |

definition := TFFunctionDefinition
parameterTypes: self parameterTypes
returnType: self returnType.

function := TFExternalFunction
fromAddress: self getHandle
definition: definition.

preparedArguments := aCollection
with: self parameterTypes
collect: [ :anArgument :aType | aType marshallToPrimitive: anArgument ].

^ self returnType marshallFromPrimitive: (self runner invokeFunction: function withArguments: preparedArguments)
]

{ #category : #accessing }
TFCallback >> parameterTypes [
^ parameterTypes
Expand Down
11 changes: 8 additions & 3 deletions src/ThreadedFFI/TFCallbackInvocation.class.st
Expand Up @@ -45,9 +45,14 @@ TFCallbackInvocation >> callbackData [

{ #category : #operations }
TFCallbackInvocation >> execute [
| returnValue |

returnValue := callback frontendCallback valueWithArguments: self arguments.
| returnValue transformedArguments |

transformedArguments := [ self arguments
with: callback parameterTypes
collect: [:anArgument :aType | aType marshallFromPrimitive: anArgument]]
on: Exception fork: [:e | e debug ] return: [ self arguments ].

returnValue := callback returnType marshallToPrimitive: (callback frontendCallback valueWithArguments: transformedArguments).

self isNull
ifTrue: [ ^ self ].
Expand Down
14 changes: 14 additions & 0 deletions src/ThreadedFFI/TFCharType.class.st
Expand Up @@ -9,3 +9,17 @@ TFCharType >> emitMarshallToPrimitive: builder [

builder send: #asInteger
]

{ #category : #marshalling }
TFCharType >> marshallFromPrimitive: aValue [

^ aValue asCharacter

]

{ #category : #marshalling }
TFCharType >> marshallToPrimitive: aValue [

^ aValue asInteger

]
14 changes: 14 additions & 0 deletions src/ThreadedFFI/TFDerivedType.class.st
Expand Up @@ -81,6 +81,20 @@ TFDerivedType >> isVoid [
^ self basicType isVoid
]

{ #category : #marshalling }
TFDerivedType >> marshallFromPrimitive: aValue [

^ aValue

]

{ #category : #marshalling }
TFDerivedType >> marshallToPrimitive: aValue [

^ aValue

]

{ #category : #'reading-writing' }
TFDerivedType >> readReturnValue: anExternalAddress [

Expand Down
7 changes: 7 additions & 0 deletions src/ThreadedFFI/TFStringType.class.st
Expand Up @@ -86,6 +86,13 @@ TFStringType >> freeValueIfNeeded: aCHeapValueHolder [

]

{ #category : #marshalling }
TFStringType >> marshallToPrimitive: aValue [

^ self prepareStringForMarshalling: aValue

]

{ #category : #writting }
TFStringType >> prepareStringForMarshalling: aStringOrExternalAddress [

Expand Down
35 changes: 33 additions & 2 deletions src/ThreadedFFI/TFStructType.class.st
Expand Up @@ -31,13 +31,25 @@ TFStructType class >> forClass: aClass withMembers: aCollectionOfMembers [
yourself
]

{ #category : #types }
TFStructType >> basicType [

^ self
]

{ #category : #size }
TFStructType >> byteSize [

self validate.
^ byteSize ifNil: [ self primitiveByteSize ]
]

{ #category : #reading }
TFStructType >> callbackReadValue: anExternalAddress [

^ targetClass fromHandle: anExternalAddress.
]

{ #category : #writing }
TFStructType >> callbackWrite: aNumber into: anExternalAddress [

Expand Down Expand Up @@ -93,6 +105,21 @@ TFStructType >> isVoid [
^ false
]

{ #category : #marshalling }
TFStructType >> marshallFromPrimitive: aValue [

(aValue isKindOf: targetClass)
ifTrue: [ ^ aValue ].

^ targetClass fromHandle: aValue
]

{ #category : #marshalling }
TFStructType >> marshallToPrimitive: aValue [

^ aValue getHandle
]

{ #category : #accessing }
TFStructType >> members [
^ members
Expand Down Expand Up @@ -134,8 +161,12 @@ TFStructType >> readReturnValue: anExternalAddress [
]

{ #category : #reading }
TFStructType >> readValue: anExternalAddress offset: anInteger [
self shouldBeImplemented.
TFStructType >> readValue: anExternalAddress offset: offset [

| address |

address := anExternalAddress pointerAt: offset.
^ targetClass fromHandle: address.
]

{ #category : #accessing }
Expand Down

0 comments on commit 96acc74

Please sign in to comment.