[squeak-dev] FFI: FFI-Pools-mt.34.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 17 10:15:05 UTC 2021


Marcel Taeumel uploaded a new version of FFI-Pools to project FFI:
http://source.squeak.org/FFI/FFI-Pools-mt.34.mcz

==================== Summary ====================

Name: FFI-Pools-mt.34
Author: mt
Time: 17 August 2021, 12:15:05.644505 pm
UUID: d3ca52ac-2ed4-d646-8721-896e19dbaaf2
Ancestors: FFI-Pools-mt.33

First attempt on extending the range of atomic types. By example, add 16-bit and 32-bit character types, which both fall-back to the already existing 8-bit character type for now.

Complements the commentary in FFI-Kernel-mt.207 and manifest the current atomic-type codes for plugin v1, sketching a possible extension in v2. Same vor #callingConventions and #errorConstants.

Note that the plugin version dictates the upper bound for supported initializers. If no matching initializer can be found, the user will be notified.

(Includes updates for ExternalPoolReadWriter to reduce the noise. But please wait for and take a look at complementary commits to FFI-Kernel.)

=============== Diff against FFI-Pools-mt.33 ===============

Item was changed:
  ----- Method: ExternalPoolReadWriter class>>initializeAtomicTypesExtra (in category 'class initialization') -----
  initializeAtomicTypesExtra
  	"Initialize C type names and format placeholders for printf, which are used during C code generation. The implementation follows the one for initialization of atomic types in ExternalType. Even though all type names are repeated here explicitely, their location in the list of atomic types is looked up dynamically. So you can change the order to improve readability."
  	
  	| type typeName cTypeName cFormatPlaceholder |
  	AtomicCTypeNames := IdentityDictionary new.
  	AtomicCFormatPlaceholders := IdentityDictionary new.
  
  	#(
  		"name			C type name			C printf % format"
  		('void'	 		'void'					'p')
  		('bool' 			'unsigned int'			'u') "See ByteArray >> #booleanAt:"
+ 
  		('uint8_t' 			'unsigned char'			'hhu') "Not 'c' to avoid conversion issues"
  		('int8_t' 		'signed char'			'hhd') "Not 'c' to avoid conversion issues"
  		('uint16_t' 		'unsigned short'		'hu')
  		('int16_t' 			'signed short'			'hd')
  		('uint32_t'			'unsigned int'			'u') "Not 'lu' bc. not unsigned long, see above"
  		('int32_t' 			'signed int'				'd') "Not 'ld' bc. not signed long, see above"
  		('uint64_t'		'unsigned long long'	'llu')
  		('int64_t'		'signed long long'		'lld')
+ 
+ 		('uchar8_t' 			'unsigned char'			'hhu') "Not 'c' to avoid conversion issues"
+ 		('char8_t' 		'signed char'			'hhd') "Not 'c' to avoid conversion issues"
+ 		('uchar16_t' 		'unsigned short'		'hu')
+ 		('char16_t' 			'signed short'			'hd')
+ 		('uchar32_t'			'unsigned int'			'u') "Not 'lu' bc. not unsigned long, see above"
+ 		('char32_t' 			'signed int'				'd') "Not 'ld' bc. not signed long, see above"
+ 
- 		('char' 			'unsigned char'			'hhu') "Not 'c' to avoid conversion issues"
- 		('schar' 		'signed char'			'hhd') "Not 'c' to avoid conversion issues"
  		('float' 			'float'					'g') "Not 'G' bc. notation in lowercase letters"
  		('double' 		'double'					'g') "Not 'G' bc. notation in lowercase letters"
  "TODO: ('longdouble' 	'long double'			'Lg')"
  	) do: [:typeSpec |
  		typeName := typeSpec first.
  		cTypeName := typeSpec second.
  		cFormatPlaceholder := '%', typeSpec third.
  		
  		type := ExternalType atomicTypeNamed: typeName.
  		AtomicCTypeNames at: type atomicType put: cTypeName.
  		AtomicCFormatPlaceholders at: type atomicType put: cFormatPlaceholder].!

Item was changed:
  SharedPool subclass: #FFIConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'FFIAtomicTypeMask FFIAtomicTypeShift FFICallFlagThreaded FFICallTypeApi FFICallTypeCDecl FFICallTypesMask FFIErrorAddressNotFound FFIErrorAttemptToPassVoid FFIErrorBadAddress FFIErrorBadArg FFIErrorBadArgs FFIErrorBadAtomicType FFIErrorBadExternalFunction FFIErrorBadExternalLibrary FFIErrorBadReturn FFIErrorCallFrameTooBig FFIErrorCallType FFIErrorCoercionFailed FFIErrorGenericError FFIErrorIntAsPointer FFIErrorInvalidPointer FFIErrorModuleNotFound FFIErrorNoModule FFIErrorNotFunction FFIErrorStructSize FFIErrorWrongType FFIFlagAtomic FFIFlagPointer FFIFlagStructure FFINoCalloutAvailable FFIStructSizeMask FFITypeBool FFITypeDoubleFloat FFITypeSignedChar16 FFITypeSignedChar32 FFITypeSignedChar8 FFITypeSignedInt16 FFITypeSignedInt32 FFITypeSignedInt64 FFITypeSignedInt8 FFITypeSingleFloat FFITypeUnsignedChar16 FFITypeUnsignedChar32 FFITypeUnsignedChar8 FFITypeUnsignedInt16 FFITypeUnsignedInt32 FFITypeUnsignedInt64 FFITypeUnsignedInt8 FFITypeVoid'
- 	classVariableNames: 'FFIAtomicTypeMask FFIAtomicTypeShift FFICallFlagThreaded FFICallTypeApi FFICallTypeCDecl FFICallTypesMask FFIErrorAddressNotFound FFIErrorAttemptToPassVoid FFIErrorBadAddress FFIErrorBadArg FFIErrorBadArgs FFIErrorBadAtomicType FFIErrorBadExternalFunction FFIErrorBadExternalLibrary FFIErrorBadReturn FFIErrorCallFrameTooBig FFIErrorCallType FFIErrorCoercionFailed FFIErrorGenericError FFIErrorIntAsPointer FFIErrorInvalidPointer FFIErrorModuleNotFound FFIErrorNoModule FFIErrorNotFunction FFIErrorStructSize FFIErrorWrongType FFIFlagAtomic FFIFlagPointer FFIFlagStructure FFINoCalloutAvailable FFIStructSizeMask FFITypeBool FFITypeDoubleFloat FFITypeSignedChar FFITypeSignedInt16 FFITypeSignedInt32 FFITypeSignedInt64 FFITypeSignedInt8 FFITypeSingleFloat FFITypeUnsignedChar FFITypeUnsignedInt16 FFITypeUnsignedInt32 FFITypeUnsignedInt64 FFITypeUnsignedInt8 FFITypeVoid'
  	poolDictionaries: ''
  	category: 'FFI-Pools'!
  
  !FFIConstants commentStamp: 'TorstenBergmann 4/27/2017 11:02' prior: 0!
  Constants definitions for FFI!

Item was added:
+ ----- Method: FFIConstants class>>initialize: (in category 'pool initialization') -----
+ initialize: aspect
+ 
+ 	| prefix currentVersion max pragma |
+ 	prefix := ('initialize', aspect capitalized) asSymbol.
+ 	currentVersion := self pluginVersion.
+ 	max := 0 -> nil.
+ 	self class methodsDo: [:method |
+ 		((method selector beginsWith: prefix) and: [(pragma := method pragmaAt: #pluginVersion:) notNil])
+ 			ifTrue: [
+ 				| targetVersion |
+ 				targetVersion := pragma argumentAt: 1.
+ 				(targetVersion <= currentVersion and: [max key < targetVersion])
+ 					ifTrue: [max := targetVersion -> method]]].
+ 			
+ 	max value ifNil: [
+ 		^ self error: 'No initializer found for: ', aspect].
+ 	max key < currentVersion ifTrue: [
+ 		self notify: 'Current FFI plugin is newer than what the image code supports. Please update your image code to initialize ', aspect, ' correctly'].
+ 	
+ 	self executeMethod: max value.!

Item was changed:
+ ----- Method: FFIConstants class>>initializeCallingConventions (in category 'pool initialization') -----
- ----- Method: FFIConstants class>>initializeCallingConventions (in category 'private - initialization') -----
  initializeCallingConventions
+ 
+ 	self initialize: #callingConventions.!
- 	"These constants map onto the flags inst var of an ExternalFunction.
- 	 The first eight bits define the calling convention.  Attribute flags
- 	 occupy bits 8 on up."
- 	"FFIConstants initializeCallingConventions"
- 	FFICallTypesMask := 255.
- 	FFICallTypeCDecl := 0.
- 	FFICallTypeApi := 1.
- 	FFICallFlagThreaded := 256!

Item was added:
+ ----- Method: FFIConstants class>>initializeCallingConventions_v1 (in category 'pool initialization') -----
+ initializeCallingConventions_v1
+ 	"These constants map onto the flags inst var of an ExternalFunction.
+ 	 The first eight bits define the calling convention.  Attribute flags
+ 	 occupy bits 8 on up."
+ 	"FFIConstants initializeCallingConventions"
+ 	<pluginVersion: 1>
+ 	FFICallTypesMask := 255.
+ 	FFICallTypeCDecl := 0.
+ 	FFICallTypeApi := 1.
+ 	FFICallFlagThreaded := 256!

Item was changed:
+ ----- Method: FFIConstants class>>initializeErrorConstants (in category 'pool initialization') -----
- ----- Method: FFIConstants class>>initializeErrorConstants (in category 'private - initialization') -----
  initializeErrorConstants
- 	"FFIConstants initializeErrorConstants"
  
+ 	self initialize: #errorConstants.!
- 	"No callout mechanism available"
- 	FFINoCalloutAvailable := -1.
- 	"generic error"
- 	FFIErrorGenericError := 0.
- 	"primitive invoked without ExternalFunction"
- 	FFIErrorNotFunction := 1.
- 	"bad arguments to primitive call"
- 	FFIErrorBadArgs := 2.
- 
- 	"generic bad argument"
- 	FFIErrorBadArg := 3.
- 	"int passed as pointer"
- 	FFIErrorIntAsPointer := 4.
- 	"bad atomic type (e.g., unknown)"
- 	FFIErrorBadAtomicType := 5.
- 	"argument coercion failed"
- 	FFIErrorCoercionFailed := 6.
- 	"Type check for non-atomic types failed"
- 	FFIErrorWrongType := 7.
- 	"struct size wrong or too large"
- 	FFIErrorStructSize := 8.
- 	"unsupported calling convention"
- 	FFIErrorCallType := 9.
- 	"cannot return the given type"
- 	FFIErrorBadReturn := 10.
- 	"bad function address"
- 	FFIErrorBadAddress := 11.
- 	"no module given but required for finding address"
- 	FFIErrorNoModule := 12.
- 	"function address not found"
- 	FFIErrorAddressNotFound := 13.
- 	"attempt to pass 'void' parameter"
- 	FFIErrorAttemptToPassVoid := 14.
- 	"module not found"
- 	FFIErrorModuleNotFound := 15.
- 	"external library invalid"
- 	FFIErrorBadExternalLibrary := 16.
- 	"external function invalid"
- 	FFIErrorBadExternalFunction := 17.
- 	"ExternalAddress points to ST memory (don't you dare to do this!!)"
- 	FFIErrorInvalidPointer := 18.
- 	"Stack frame required more than 16k bytes to pass arguments."
- 	FFIErrorCallFrameTooBig := 19!

Item was added:
+ ----- Method: FFIConstants class>>initializeErrorConstants_v1 (in category 'pool initialization') -----
+ initializeErrorConstants_v1
+ 	"FFIConstants initializeErrorConstants"
+ 	<pluginVersion: 1>
+ 	"No callout mechanism available"
+ 	FFINoCalloutAvailable := -1.
+ 	"generic error"
+ 	FFIErrorGenericError := 0.
+ 	"primitive invoked without ExternalFunction"
+ 	FFIErrorNotFunction := 1.
+ 	"bad arguments to primitive call"
+ 	FFIErrorBadArgs := 2.
+ 
+ 	"generic bad argument"
+ 	FFIErrorBadArg := 3.
+ 	"int passed as pointer"
+ 	FFIErrorIntAsPointer := 4.
+ 	"bad atomic type (e.g., unknown)"
+ 	FFIErrorBadAtomicType := 5.
+ 	"argument coercion failed"
+ 	FFIErrorCoercionFailed := 6.
+ 	"Type check for non-atomic types failed"
+ 	FFIErrorWrongType := 7.
+ 	"struct size wrong or too large"
+ 	FFIErrorStructSize := 8.
+ 	"unsupported calling convention"
+ 	FFIErrorCallType := 9.
+ 	"cannot return the given type"
+ 	FFIErrorBadReturn := 10.
+ 	"bad function address"
+ 	FFIErrorBadAddress := 11.
+ 	"no module given but required for finding address"
+ 	FFIErrorNoModule := 12.
+ 	"function address not found"
+ 	FFIErrorAddressNotFound := 13.
+ 	"attempt to pass 'void' parameter"
+ 	FFIErrorAttemptToPassVoid := 14.
+ 	"module not found"
+ 	FFIErrorModuleNotFound := 15.
+ 	"external library invalid"
+ 	FFIErrorBadExternalLibrary := 16.
+ 	"external function invalid"
+ 	FFIErrorBadExternalFunction := 17.
+ 	"ExternalAddress points to ST memory (don't you dare to do this!!)"
+ 	FFIErrorInvalidPointer := 18.
+ 	"Stack frame required more than 16k bytes to pass arguments."
+ 	FFIErrorCallFrameTooBig := 19!

Item was changed:
+ ----- Method: FFIConstants class>>initializeTypeConstants (in category 'pool initialization') -----
- ----- Method: FFIConstants class>>initializeTypeConstants (in category 'private - initialization') -----
  initializeTypeConstants
- 	"type void"
- 	FFITypeVoid := 0.
  
+ 	self initialize: #typeConstants.!
- 	"type bool"
- 	FFITypeBool := 1.
- 
- 	"basic integer types.
- 	note: (integerType anyMask: 1) = integerType isSigned"
- 
- 	FFITypeUnsignedInt8 := 2.
- 	FFITypeSignedInt8 := 3.
- 	FFITypeUnsignedInt16 := 4.
- 	FFITypeSignedInt16 := 5.
- 	FFITypeUnsignedInt32 := 6.
- 	FFITypeSignedInt32 := 7.
- 	FFITypeUnsignedInt64 := 8.
- 	FFITypeSignedInt64 := 9.
- 
- 	"special integer types"
- 	FFITypeUnsignedChar := 10.
- 	FFITypeSignedChar := 11.
- 
- 	"float types"
- 	FFITypeSingleFloat := 12.
- 	FFITypeDoubleFloat := 13.
- 
- 	"type flags"
- 	FFIFlagAtomic := 16r40000. "type is atomic"
- 	FFIFlagPointer := 16r20000. "type is pointer to base type"
- 	FFIFlagStructure := 16r10000. "baseType is structure of 64k length"
- 	FFIStructSizeMask := 16rFFFF. "mask for max size of structure"
- 	FFIAtomicTypeMask := 16r0F000000. "mask for atomic type spec"
- 	FFIAtomicTypeShift := 24. "shift for atomic type"
- !

Item was added:
+ ----- Method: FFIConstants class>>initializeTypeConstants_v1 (in category 'pool initialization') -----
+ initializeTypeConstants_v1
+ 	<pluginVersion: 1>
+ 
+ 	"type void"
+ 	FFITypeVoid := 0.
+ 
+ 	"type bool"
+ 	FFITypeBool := 1.
+ 
+ 	"basic integer types.
+ 	note: (integerType anyMask: 1) = integerType isSigned"
+ 
+ 	FFITypeUnsignedInt8 := 2.
+ 	FFITypeSignedInt8 := 3.
+ 	FFITypeUnsignedInt16 := 4.
+ 	FFITypeSignedInt16 := 5.
+ 	FFITypeUnsignedInt32 := 6.
+ 	FFITypeSignedInt32 := 7.
+ 	FFITypeUnsignedInt64 := 8.
+ 	FFITypeSignedInt64 := 9.
+ 
+ 	"special integer types"
+ 	FFITypeUnsignedChar8 := 10.
+ 	FFITypeSignedChar8 := 11.
+ 	FFITypeUnsignedChar16 := 10. "v1 is for backwards compatibility"
+ 	FFITypeSignedChar16 := 11. "v1 is for backwards compatibility"
+ 	FFITypeUnsignedChar32 := 10. "v1 is for backwards compatibility"
+ 	FFITypeSignedChar32 := 11. "v1 is for backwards compatibility"
+ 
+ 	"float types"
+ 	FFITypeSingleFloat := 12.
+ 	FFITypeDoubleFloat := 13.
+ 
+ 	"type flags"
+ 	FFIFlagAtomic := 16r40000. "type is atomic"
+ 	FFIFlagPointer := 16r20000. "type is pointer to base type"
+ 	FFIFlagStructure := 16r10000. "baseType is structure of 64k length"
+ 	FFIStructSizeMask := 16rFFFF. "mask for max size of structure"
+ 	FFIAtomicTypeMask := 16r0F000000. "mask for atomic type spec"
+ 	FFIAtomicTypeShift := 24. "shift for atomic type"
+ !

Item was added:
+ ----- Method: FFIConstants class>>initializeTypeConstants_v2 (in category 'pool initialization') -----
+ initializeTypeConstants_v2
+ 	<pluginVersion: 2>
+ 	
+ 	self halt. "Not fully specified and still to be discussed."
+ 	
+ 	"type void"
+ 	FFITypeVoid := 0.
+ 
+ 	"type bool"
+ 	FFITypeBool := 1.
+ 
+ 	"basic integer types.
+ 	note: (integerType anyMask: 1) = integerType isSigned"
+ 
+ 	FFITypeUnsignedInt8 := 2.
+ 	FFITypeSignedInt8 := 3.
+ 	FFITypeUnsignedInt16 := 4.
+ 	FFITypeSignedInt16 := 5.
+ 	FFITypeUnsignedInt32 := 6.
+ 	FFITypeSignedInt32 := 7.
+ 	FFITypeUnsignedInt64 := 8.
+ 	FFITypeSignedInt64 := 9.
+ 
+ 	"special integer types"
+ 	FFITypeUnsignedChar8 := 10.
+ 	FFITypeSignedChar8 := 11.
+ 	FFITypeUnsignedChar16 := 12.
+ 	FFITypeSignedChar16 := 13.
+ 	FFITypeUnsignedChar32 := 14.
+ 	FFITypeSignedChar32 := 15.
+ 
+ 	"float types"
+ 	FFITypeSingleFloat := 16.
+ 	FFITypeDoubleFloat := 17.
+ 
+ 	"type flags"
+ 	FFIFlagAtomic := 16r40000. "type is atomic"
+ 	FFIFlagPointer := 16r20000. "type is pointer to base type"
+ 	FFIFlagStructure := 16r10000. "baseType is structure of 64k length"
+ 	FFIStructSizeMask := 16rFFFF. "mask for max size of structure"
+ 	FFIAtomicTypeMask := 16r0F000000. "mask for atomic type spec"
+ 	FFIAtomicTypeShift := 24. "shift for atomic type"
+ !

Item was added:
+ ----- Method: FFIConstants class>>pluginVersion (in category 'pool initialization') -----
+ pluginVersion
+ 	"See FFIPlatformDescription."
+ 	<primitive: #primitivePluginVersion module: #SqueakFFIPrims>
+ 	^ 1!



More information about the Squeak-dev mailing list