diff --git a/src/UnifiedFFI-Tests/FFIValueHolderTest.class.st b/src/UnifiedFFI-Tests/FFIValueHolderTest.class.st index 5c942909ba2..6e11949ac52 100644 --- a/src/UnifiedFFI-Tests/FFIValueHolderTest.class.st +++ b/src/UnifiedFFI-Tests/FFIValueHolderTest.class.st @@ -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 | @@ -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 ] diff --git a/src/UnifiedFFI/FFIArray.class.st b/src/UnifiedFFI/FFIArray.class.st index 7fffbb166b5..e5caadbf68e 100644 --- a/src/UnifiedFFI/FFIArray.class.st +++ b/src/UnifiedFFI/FFIArray.class.st @@ -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 ] +] diff --git a/src/UnifiedFFI/FFIEnumeration.class.st b/src/UnifiedFFI/FFIEnumeration.class.st index da16e6ec392..fb9c5362a5a 100644 --- a/src/UnifiedFFI/FFIEnumeration.class.st +++ b/src/UnifiedFFI/FFIEnumeration.class.st @@ -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 diff --git a/src/UnifiedFFI/FFIExternalObjectType.class.st b/src/UnifiedFFI/FFIExternalObjectType.class.st index 4f461233993..2212cf90c37 100644 --- a/src/UnifiedFFI/FFIExternalObjectType.class.st +++ b/src/UnifiedFFI/FFIExternalObjectType.class.st @@ -11,8 +11,9 @@ Class { { #category : 'initialization' } FFIExternalObjectType >> initialize [ + super initialize. - pointerArity := self class naturalPointerArity + pointerArity := self naturalPointerArity ] { #category : 'accessing' } diff --git a/src/UnifiedFFI/FFIExternalType.class.st b/src/UnifiedFFI/FFIExternalType.class.st index edd2eed128b..d0e4de5c7ea 100644 --- a/src/UnifiedFFI/FFIExternalType.class.st +++ b/src/UnifiedFFI/FFIExternalType.class.st @@ -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. @@ -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' } diff --git a/src/UnifiedFFI/FFIOop.class.st b/src/UnifiedFFI/FFIOop.class.st index 9b6db2cbb76..5c0e639422c 100644 --- a/src/UnifiedFFI/FFIOop.class.st +++ b/src/UnifiedFFI/FFIOop.class.st @@ -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' } diff --git a/src/UnifiedFFI/FFIReferenceValueHolder.class.st b/src/UnifiedFFI/FFIReferenceValueHolder.class.st index 9c7d90ce573..b8f4e86eff1 100644 --- a/src/UnifiedFFI/FFIReferenceValueHolder.class.st +++ b/src/UnifiedFFI/FFIReferenceValueHolder.class.st @@ -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 [ diff --git a/src/UnifiedFFI/FFIStructure.class.st b/src/UnifiedFFI/FFIStructure.class.st index a8e8d18bfa4..59950db20d0 100644 --- a/src/UnifiedFFI/FFIStructure.class.st +++ b/src/UnifiedFFI/FFIStructure.class.st @@ -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 ] ]. @@ -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 ] @@ -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 +]