diff --git a/src/UnifiedFFI-Tests/FFIFunctionResolutionTest.class.st b/src/UnifiedFFI-Tests/FFIFunctionResolutionTest.class.st index 465ba0dc495..bf169ced57d 100644 --- a/src/UnifiedFFI-Tests/FFIFunctionResolutionTest.class.st +++ b/src/UnifiedFFI-Tests/FFIFunctionResolutionTest.class.st @@ -308,6 +308,19 @@ FFIFunctionResolutionTest >> testResolveConstantSelfShouldResolveToExternalObjec self assert: argument resolvedType equals: (receiver class asExternalTypeOn: nil) ] +{ #category : #tests } +FFIFunctionResolutionTest >> testResolveConstantSelfStringInStrictResolverFails [ + + | argument resolver | + argument := FFIConstantArgument new + value: 17; + yourself. + + resolver := FFICallout new. + resolver beStrict. + self should: [argument resolveUsing: resolver] raise: FFIUnsupportedUntypedLiteral +] + { #category : #tests } FFIFunctionResolutionTest >> testResolveConstantSelfStringShouldSetConstantLoader [ diff --git a/src/UnifiedFFI/FFICallout.class.st b/src/UnifiedFFI/FFICallout.class.st index 40805a6112e..fa12663b05b 100644 --- a/src/UnifiedFFI/FFICallout.class.st +++ b/src/UnifiedFFI/FFICallout.class.st @@ -24,7 +24,8 @@ Class { 'requestor', 'methodArgs', 'receiver', - 'method' + 'method', + 'resolutionMode' ], #classVars : [ 'TypeAliases' @@ -136,6 +137,12 @@ FFICallout >> argName: argName indirectIndex: anIndex type: aTypeName ptrArity: yourself ] +{ #category : #configuration } +FFICallout >> beStrict [ + + resolutionMode := FFIStrictResolutionMode new +] + { #category : #accessing } FFICallout >> callType: aCallType [ aCallType == #cdecl ifTrue: [ ^ self cdecl ]. @@ -159,7 +166,8 @@ FFICallout >> indirectLoader: aLoader byIndex: anIndex [ { #category : #initialization } FFICallout >> initialize [ super initialize. - options := Dictionary new + options := Dictionary new. + resolutionMode := FFIInferenceResolutionMode new ] { #category : #private } @@ -369,6 +377,12 @@ FFICallout >> resolveType: aTypeName [ ^ self error: 'Unable to resolve external type: ' , aTypeName asString ] +{ #category : #'spec parsing' } +FFICallout >> resolveUntypedArgument: anArgument [ + + ^ resolutionMode resolveUndeclaredTypeForArgument: anArgument withResolver: self +] + { #category : #'spec parsing' } FFICallout >> returnType: aType [ aType first = 'receiver' @@ -401,3 +415,9 @@ FFICallout >> sender: aSenderContext [ FFICallout >> typeName: aName pointerArity: ptrArity [ ^ (self resolveType: aName) pointerArity: ptrArity ] + +{ #category : #errors } +FFICallout >> unsupportedUntypedLiteral: aLiteral [ + + FFIUnsupportedUntypedLiteral signalFor: aLiteral +] diff --git a/src/UnifiedFFI/FFIInferenceResolutionMode.class.st b/src/UnifiedFFI/FFIInferenceResolutionMode.class.st new file mode 100644 index 00000000000..6f81ecfc99b --- /dev/null +++ b/src/UnifiedFFI/FFIInferenceResolutionMode.class.st @@ -0,0 +1,37 @@ +" +I resolve ffi call-out arguments in a non-strict way. +This is the backwards compatibility mode and should not be used unless you know what you do. + +I try to guess what type to use for a literal. +For example, for a self reference I can guess it by looking at the type of the class of self. +However, some types are problematic. For example, ints and floats can have different size/precisions. +" +Class { + #name : #FFIInferenceResolutionMode, + #superclass : #Object, + #category : #'UnifiedFFI-Callouts' +} + +{ #category : #resolution } +FFIInferenceResolutionMode >> resolveUndeclaredTypeForArgument: aFFIValueArgument withResolver: aResolver [ + + (aFFIValueArgument value isNil + or: [aFFIValueArgument value = 'nil' + or: [ aFFIValueArgument value = 'NULL' ]]) + ifTrue: [ ^ (aResolver resolveType: #'void *') ]. + (#(true false) includes: aFFIValueArgument value) + ifTrue: [ ^ aResolver resolveType: #bool ]. + aFFIValueArgument value isInteger + ifTrue: [ ^ (aFFIValueArgument value >=0 + ifTrue: [ aResolver resolveType: #uint32 ] + ifFalse: [ aResolver resolveType: #int32 ]) ]. + (aFFIValueArgument value == #self) ifTrue: [ + ^ (aResolver requestor asExternalTypeOn: aResolver) + prepareAsSelfFromCalloutDeclaration ]. + + ^ aFFIValueArgument value isSymbol + ifTrue: [ + "This is actually a class variable with a value..." + aResolver resolveType: aFFIValueArgument value ] + ifFalse: [ aResolver unsupportedUntypedLiteral: aFFIValueArgument value ] +] diff --git a/src/UnifiedFFI/FFIStrictResolutionMode.class.st b/src/UnifiedFFI/FFIStrictResolutionMode.class.st new file mode 100644 index 00000000000..c4925583079 --- /dev/null +++ b/src/UnifiedFFI/FFIStrictResolutionMode.class.st @@ -0,0 +1,14 @@ +" +I resolve arguments strictly: if they have no type declaration I throw an exception. +" +Class { + #name : #FFIStrictResolutionMode, + #superclass : #Object, + #category : #'UnifiedFFI-Callouts' +} + +{ #category : #resolution } +FFIStrictResolutionMode >> resolveUndeclaredTypeForArgument: aFFIValueArgument withResolver: aResolver [ + + aResolver unsupportedUntypedLiteral: aFFIValueArgument value +] diff --git a/src/UnifiedFFI/FFIUndefinedTypeDeclaration.class.st b/src/UnifiedFFI/FFIUndefinedTypeDeclaration.class.st index ab619d24323..ff945bcc70c 100644 --- a/src/UnifiedFFI/FFIUndefinedTypeDeclaration.class.st +++ b/src/UnifiedFFI/FFIUndefinedTypeDeclaration.class.st @@ -11,31 +11,7 @@ FFIUndefinedTypeDeclaration >> isUndefined [ ] { #category : #resolution } -FFIUndefinedTypeDeclaration >> resolveUsing: aResolver forArgument: aFFIValueArgument [ +FFIUndefinedTypeDeclaration >> resolveUsing: aResolver forArgument: aFFIFunctionArgument [ - (aFFIValueArgument value isNil - or: [aFFIValueArgument value = 'nil' - or: [ aFFIValueArgument value = 'NULL' ]]) - ifTrue: [ ^ (aResolver resolveType: #'void *') ]. - (#(true false) includes: aFFIValueArgument value) - ifTrue: [ ^ aResolver resolveType: #bool ]. - aFFIValueArgument value isInteger - ifTrue: [ ^ (aFFIValueArgument value >=0 - ifTrue: [ aResolver resolveType: #uint32 ] - ifFalse: [ aResolver resolveType: #int32 ]) ]. - (aFFIValueArgument value == #self) ifTrue: [ - ^ (aResolver requestor asExternalTypeOn: aResolver) - prepareAsSelfFromCalloutDeclaration ]. - - ^ aFFIValueArgument value isSymbol - ifTrue: [ - "This is actually a class variable with a value..." - aResolver resolveType: aFFIValueArgument value ] - ifFalse: [ self unsupportedUntypedLiteral: aFFIValueArgument value ] -] - -{ #category : #errors } -FFIUndefinedTypeDeclaration >> unsupportedUntypedLiteral: aLiteral [ - - FFIUnsupportedUntypedLiteral signalFor: aLiteral + ^ aResolver resolveUntypedArgument: aFFIFunctionArgument ]