Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
36 changes: 32 additions & 4 deletions src/UnifiedFFI-Tests/FFIValueHolderTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -321,6 +321,33 @@ FFIValueHolderTest >> testCallStructPointerPointerWithValueHolder [
holder value getHandle free.
]

{ #category : 'tests' }
FFIValueHolderTest >> testCallStructureWithReference [
| struct holder result |

struct := FFITestStructure new.
holder := struct referenceTo.

"this simulates a c function like this:
int aFunction(FFITestStructure *aValue) {
aValue->byteValue = 42;
return 1;
}"
FFICallbackFunctionResolution
registerCallback: (FFICallback
signature: #(int (void *aValue))
block: [ :aValue |
(FFITestStructure fromHandle: aValue) byte: 42.
1 ])
as: #TestStructureValueHolder.
self assert: struct byte equals: 0.

result := self ffiMethodStructure: holder.

self assert: result equals: 1.
self assert: struct byte equals: 42
]

{ #category : 'tests' }
FFIValueHolderTest >> testCallStructureWithValueHolder [
| holder result resultStruct |
Expand Down Expand Up @@ -364,11 +391,12 @@ FFIValueHolderTest >> testOpaqueObjectTypeCanBeHolded [
FFIValueHolderTest >> testStructureTypeCanBeHolded [
| holder |

"a holder of the structure is the handle of the structure itself, since from the POV
of uFFI is the same to pass `AStruct arg` than `AStruct *arg` sinie the argument
mangling will be aquivalent (this maybe should be review)?"

holder := FFITestStructure newValueHolder.
self assert: holder type class equals: FFITestStructure.
self assert: (holder getHandle isKindOf: ByteArray).
self assert: holder getHandle size equals: FFITestStructure newBuffer size.
"this can't be like this (the structure tries to be filled with the handle)"
"holder value: (structClass fromHandle: (ExternalAddress fromAddress: 42)).
self assert: holder value getHandle equals: (ExternalAddress fromAddress: 42)"
self assert: holder getHandle size equals: FFITestStructure structureSize
]
12 changes: 12 additions & 0 deletions src/UnifiedFFI/FFIArray.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -173,3 +173,15 @@ FFIArray class >> type: aType size: elements [
type := aType.
numberOfElements := elements
]

{ #category : 'converting' }
FFIArray >> packToArity: arity [
"in fact, an FFIArray has a 'natural' arity of 1 + the arity of the contained type.
Which means to box it (pack it) to an arity, first we have to substract that value."
| realArity |

realArity := arity - self type naturalPointerArity.
^ realArity > 1
ifTrue: [ super packToArity: realArity ]
ifFalse: [ self ]
]
7 changes: 7 additions & 0 deletions src/UnifiedFFI/FFIEnumeration.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -312,10 +312,17 @@ FFIEnumeration class >> representationType [

{ #category : 'comparing' }
FFIEnumeration >> = anEnumInst [

^ self class == anEnumInst class
and: [ self value = anEnumInst value ]
]

{ #category : 'comparing' }
FFIEnumeration >> hash [

^ self class hash bitXor: self value
]

{ #category : 'accessing' }
FFIEnumeration >> item [
^ self class itemAt: value
Expand Down
3 changes: 2 additions & 1 deletion src/UnifiedFFI/FFIExternalObjectType.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,9 @@ Class {

{ #category : 'initialization' }
FFIExternalObjectType >> initialize [

super initialize.
pointerArity := self class naturalPointerArity
pointerArity := self naturalPointerArity
]

{ #category : 'accessing' }
Expand Down
8 changes: 7 additions & 1 deletion src/UnifiedFFI/FFIExternalType.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -279,6 +279,12 @@ FFIExternalType >> loader: aLoader [
loader := aLoader
]

{ #category : 'accessing' }
FFIExternalType >> naturalPointerArity [

^ self class naturalPointerArity
]

{ #category : 'testing' }
FFIExternalType >> needsArityPacking [
"Regular types needs to be ''rolled'' if they are passed as pointers to its calling functions.
Expand All @@ -294,7 +300,7 @@ FFIExternalType >> needsArityPacking [
Means that if I have a type that is naturally a pointer (for example an ExternalAddress, who
is a 'void*'), it will have a natural arity of 1, then I pack if arity is bigger.
Other cases could need to be rolled when pointer arity is diffrent."
^ self pointerArity > self class naturalPointerArity
^ self pointerArity > self naturalPointerArity
]

{ #category : 'testing' }
Expand Down
4 changes: 1 addition & 3 deletions src/UnifiedFFI/FFIOop.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,7 @@ FFIOop >> basicHandle: aHandle at: index [

{ #category : 'private' }
FFIOop >> basicHandle: aHandle at: index put: value [
self error: 'Not sure I want to do this.'
"But it would be like this:
aHandle pointerAt: index put: value"
aHandle pointerAt: index put: value
]

{ #category : 'accessing' }
Expand Down
8 changes: 8 additions & 0 deletions src/UnifiedFFI/FFIReferenceValueHolder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,14 @@ FFIReferenceValueHolder class >> newType: aType [
handle: FFIValueHolderHandle new
]

{ #category : 'instance creation' }
FFIReferenceValueHolder class >> newType: aType handle: aHandle size: aSize [

^ (self newType: aType handle: aHandle)
typeSize: aSize;
yourself
]

{ #category : 'instance creation' }
FFIReferenceValueHolder class >> newType: aType size: aNumber [

Expand Down
22 changes: 20 additions & 2 deletions src/UnifiedFFI/FFIStructure.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -154,6 +154,11 @@ FFIStructure class >> compileFields: specArray withAccessors: aSymbol [
{ #category : 'private' }
FFIStructure class >> compileMethodNamed: aSymbol code: aString classified: protocol [

"If we detect we have a method in the class with the right code but an equivalent is already in a superclass we can remove it to clean."
self
compiledMethodAt: aSymbol
ifPresent: [ :method | method sourceCode = aString and: [ method hasEquivalentMethodInSuperclass ifTrue: [ ^ method removeFromSystem ] ] ].

"If we already have the method we do not need to compile it. The method can come from a superclass having the same fields"
(self lookupSelector: aSymbol) ifNotNil: [ :method | method sourceCode = aString ifTrue: [ ^ self ] ].

Expand Down Expand Up @@ -312,9 +317,12 @@ FFIStructure class >> newBuffer [

{ #category : 'instance creation' }
FFIStructure class >> newValueHolder [

| struct |

struct := self new.
^ FFIReferenceValueHolder
newType: self new
newType: struct
handle: struct getHandle
size: self structureSize
]

Expand Down Expand Up @@ -446,3 +454,13 @@ FFIStructure >> printOn: aStream [
] separatedBy: [ aStream cr ].
aStream cr; nextPut: $)"
]

{ #category : 'converting' }
FFIStructure >> referenceTo [
"In fact, structures in uFFI are always passed by reference, then a referenceTo
it will always be itself"

^ FFIValueHolder
newType: self
handle: self getHandle
]