[squeak-dev] FFI: FFI-Kernel-mt.205.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Aug 16 07:12:49 UTC 2021


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

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

Name: FFI-Kernel-mt.205
Author: mt
Time: 16 August 2021, 9:12:47.322631 am
UUID: f4fcd757-5ecb-ff44-b8b7-31df187c9721
Ancestors: FFI-Kernel-eem.204

Complements FFI-Pools-mt.33

=============== Diff against FFI-Kernel-eem.204 ===============

Item was changed:
  ----- Method: ExternalType class>>byte (in category 'type constants') -----
  byte
+ 	"For convenience, byte defaults to unsigned 8-bit integer."
+ 	
+ 	^ self uint8_t!
- 	"byte defaults to unsigned byte"
- 	^self unsignedByte!

Item was changed:
  ----- Method: ExternalType class>>char (in category 'type constants') -----
  char
  	"char defaults to unsigned char"
+ 	
+ 	self flag: #discuss. "mt: Shouldn't this rather be signed 8-bit character type?"
  	^self unsignedChar!

Item was changed:
  ----- Method: ExternalType class>>initialize (in category 'class initialization') -----
  initialize
  	"
  	ExternalType initialize
  	"
+ 	self initializeAtomicTypeNames.
- 	self initializeFFIConstants.
  	
  	self initializeAtomicTypes.
  	self initializeAtomicSends.
  	
  	self initializeStructureTypes.
  	
  	self initializeArrayClasses.!

Item was added:
+ ----- Method: ExternalType class>>initializeAtomicTypeNames (in category 'class initialization') -----
+ initializeAtomicTypeNames
+ 	"ExternalType initialize"
+ 
+ 	AtomicTypeNames := IdentityDictionary newFrom: {
+ 		FFITypeVoid -> #'void'.
+ 		FFITypeBool -> #'bool'.
+ 		
+ 		FFITypeUnsignedInt8 -> #'uint8_t'.
+ 		FFITypeSignedInt8 -> #'int8_t'.
+ 		FFITypeUnsignedInt16 -> #'uint16_t'.
+ 		FFITypeSignedInt16 -> #'int16_t'.
+ 		FFITypeUnsignedInt32 -> #'uint32_t'.
+ 		FFITypeSignedInt32 -> #'int32_t'.
+ 		FFITypeUnsignedInt64 -> #'uint64_t'.
+ 		FFITypeSignedInt64 -> #'int64_t'.
+ 		
+ 		FFITypeUnsignedChar -> #'char'.
+ 		FFITypeSignedChar -> #'schar'.
+ 		
+ 		FFITypeSingleFloat -> #'float'.
+ 		FFITypeDoubleFloat -> #'double'
+ 	}.!

Item was changed:
  ----- Method: ExternalType class>>initializeAtomicTypes (in category 'class initialization') -----
  initializeAtomicTypes
  	"(Re-)initialize all atomic types. Preserves object identity of all involved types. If the amount of types changed, use #resetAllAtomicTypes instead."
  		
  	| atomicType byteSize type typeName byteAlignment |
- 	self flag: #ffiLongVsInt. "For a discussion about long vs. int see http://forum.world.st/Re-squeak-dev-64-bit-FFI-was-porting-Croquet-to-Squeak6-0-alpha-tp5113318.html."
- 
  	self basicInitializeAtomicTypes.
  	self invalidateAtomicTypes.
  	
  	#(
  		"name		atomic id		byte size	byte alignment"
+ 		(#'void' 		0 				0			0) "No non-pointer support in calls. Duh. ;-)"
+ 		(#'bool' 		1 				1			1) "No pointer support in calls."
+ 		(#'uint8_t' 		2 				1			1)
+ 		(#'int8_t' 	3 				1			1)
+ 		(#'uint16_t' 	4 				2			2)
+ 		(#'int16_t' 		5 				2			2)
+ 		(#'uint32_t' 	6 				4 			4)
+ 		(#'int32_t' 		7 				4			4)
+ 		(#'uint64_t' 8 				8			8) "v.i."
+ 		(#'int64_t' 	9 				8			8) "v.i."
+ 		(#'char' 		10 				1			1)
+ 		(#'schar' 	11 				1			1)
+ 		(#'float' 		12 				4			4)
+ 		(#'double' 	13 				8			8) "v.i."
- 		('void' 		0 				0			0) "No non-pointer support in calls. Duh. ;-)"
- 		('bool' 		1 				1			1) "No pointer support in calls."
- 		('byte' 		2 				1			1)
- 		('sbyte' 	3 				1			1)
- 		('ushort' 	4 				2			2)
- 		('short' 		5 				2			2)
- "!!!!!!"	('ulong' 	6 				4 "!!!!!!"		4)
- "!!!!!!"	('long' 		7 				4 "!!!!!!"		4)
- 		('ulonglong' 8 				8			8) "v.i."
- 		('longlong' 	9 				8			8) "v.i."
- 		('char' 		10 				1			1)
- 		('schar' 	11 				1			1)
- 		('float' 		12 				4			4)
- 		('double' 	13 				8			8) "v.i."
  "TODO: ('longdouble' 14			10			16? 4?)"
  	) do:[:typeSpec| | compiled |
  		typeName := typeSpec first.
  		atomicType := typeSpec second.
+ 		self assert: [(AtomicTypeNames keyAtValue: typeName) = atomicType].
+ 		
  		byteSize := typeSpec third.
  		byteAlignment := typeSpec fourth.
  		
  		"0) On 32-bits Windows and MacOS, double and long long have an alignment of 8. But on 32-bit Linux, their alignment is 4. But not on a 32-bit Raspberry Pi OS."
  		(FFIPlatformDescription current wordSize = 4
  			and: [FFIPlatformDescription current isUnix
  			and: [FFIPlatformDescription current isARM not]]) ifTrue: [
+ 				(#('double' 'int64_t' 'uint64_t') includes: typeName) ifTrue: [
- 				(#('double' 'longlong' 'ulonglong') includes: typeName) ifTrue: [
  					byteAlignment := 4]].
  		
  		"1) Regular type"
  		type := (AtomicTypes at: typeName).
  		compiled := WordArray with: ((byteSize bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: byteAlignment.
  		
  		"2) Pointer type"
  		type := type asPointerType.
  		compiled := WordArray with: ((self pointerSpec bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: self pointerAlignment.
  	].!

Item was removed:
- ----- Method: ExternalType class>>initializeFFIConstants (in category 'class initialization') -----
- initializeFFIConstants
- 	"ExternalType initialize"
- 	FFIConstants initialize. "ensure proper initialization"
- 	AtomicTypeNames := IdentityDictionary new.
- 	AtomicTypeNames
- 		at: FFITypeVoid put: 'void';
- 		at: FFITypeBool put: 'bool';
- 		at: FFITypeUnsignedByte put: 'byte';
- 		at: FFITypeSignedByte put: 'sbyte';
- 		at: FFITypeUnsignedShort put: 'ushort';
- 		at: FFITypeSignedShort put: 'short';
- 		flag: #ffiLongVsInt;
- 		at: FFITypeUnsignedInt put: 'ulong';
- 		at: FFITypeSignedInt put: 'long';
- 		at: FFITypeUnsignedLongLong put: 'ulonglong';
- 		at: FFITypeSignedLongLong put: 'longlong';
- 		at: FFITypeUnsignedChar put: 'char';
- 		at: FFITypeSignedChar put: 'schar';
- 		at: FFITypeSingleFloat put: 'float';
- 		at: FFITypeDoubleFloat put: 'double';
- 	yourself.!

Item was changed:
  ----- Method: ExternalType class>>int (in category 'type constants') -----
  int
  
+ 	self flag: #deprecated.
+ 	^ self int32_t!
- 	self flag: #ffiLongVsInt.
- 	^ self long!

Item was changed:
  ----- Method: ExternalType class>>int16_t (in category 'type constants - stdint.h') -----
  int16_t
  
+ 	^ AtomicTypes at: 'int16_t'!
- 	^ self signedShort!

Item was changed:
  ----- Method: ExternalType class>>int32_t (in category 'type constants - stdint.h') -----
  int32_t
  
+ 	^ AtomicTypes at: 'int32_t'!
- 	^ self signedInt!

Item was changed:
  ----- Method: ExternalType class>>int64_t (in category 'type constants - stdint.h') -----
  int64_t
  
+ 	^ AtomicTypes at: 'int64_t'!
- 	^ self signedLongLong!

Item was changed:
  ----- Method: ExternalType class>>int8_t (in category 'type constants - stdint.h') -----
  int8_t
  
+ 	^ AtomicTypes at: 'int8_t'!
- 	^ self signedByte!

Item was changed:
  ----- Method: ExternalType class>>long (in category 'type constants') -----
  long
  
+ 	self flag: #deprecated.	
+ 	^ self int32_t!
- 	self flag: #ffiLongVsInt.
- 	^ self signedLong!

Item was changed:
  ----- Method: ExternalType class>>longlong (in category 'type constants') -----
  longlong
+ 
+ 	self flag: #deprecated.	
+ 	^ self int64_t!
- 	^ self signedLongLong!

Item was changed:
  ----- Method: ExternalType class>>resetAllAtomicTypes (in category 'housekeeping') -----
  resetAllAtomicTypes
  	"Warning: This call is only required if you change the initialization for AtomicTypes."
  
+ 	AtomicTypeNames := nil.
+ 	self initializeAtomicTypeNames.
+ 
  	AtomicTypes := nil.
  	self initializeAtomicTypes.
  
  	AtomicSends := nil.
  	self initializeAtomicSends.
  	
  	"Now also reset everything that depends on atomic types."	
  	self resetAllStructureTypes.!

Item was changed:
  ----- Method: ExternalType class>>sbyte (in category 'type constants') -----
  sbyte
+ 
+ 	self flag: #deprecated.
+ 	^self int8_t!
- 	^self signedByte!

Item was changed:
  ----- Method: ExternalType class>>short (in category 'type constants') -----
  short
+ 
+ 	self flag: #deprecated.
+ 	^self int16_t!
- 	^self signedShort!

Item was changed:
  ----- Method: ExternalType class>>signedByte (in category 'type constants') -----
  signedByte
+ 
+ 	self flag: #deprecated.
+ 	^ self int8_t!
- 	^AtomicTypes at: 'sbyte'!

Item was changed:
  ----- Method: ExternalType class>>signedInt (in category 'type constants') -----
  signedInt
  
+ 	self flag: #deprecated.
- 	self flag: #ffiLongVsInt.
  	^ self signedLong!

Item was changed:
  ----- Method: ExternalType class>>signedLong (in category 'type constants') -----
  signedLong
  
+ 	self flag: #deprecated.
+ 	^ self int32_t!
- 	self flag: #ffiLongVsInt.
- 	^AtomicTypes at: 'long'!

Item was changed:
  ----- Method: ExternalType class>>signedLongLong (in category 'type constants') -----
  signedLongLong
+ 
+ 	self flag: #deprecated.	
+ 	^ self int64_t!
- 	^AtomicTypes at: 'longlong'!

Item was changed:
  ----- Method: ExternalType class>>signedShort (in category 'type constants') -----
  signedShort
+ 
+ 	self flag: #deprecated.	
+ 	^ self int16_t!
- 	^AtomicTypes at: 'short'!

Item was changed:
  ----- Method: ExternalType class>>uint (in category 'type constants') -----
  uint
  
+ 	self flag: #deprecated.
+ 	^ self uint32_t!
- 	self flag: #ffiLongVsInt.
- 	^ self ulong!

Item was changed:
  ----- Method: ExternalType class>>uint16_t (in category 'type constants - stdint.h') -----
  uint16_t
  
+ 	^ AtomicTypes at: 'uint16_t'!
- 	^ self unsignedShort!

Item was changed:
  ----- Method: ExternalType class>>uint32_t (in category 'type constants - stdint.h') -----
  uint32_t
  
+ 	^ AtomicTypes at: 'uint32_t'!
- 	^ self unsignedInt!

Item was changed:
  ----- Method: ExternalType class>>uint64_t (in category 'type constants - stdint.h') -----
  uint64_t
  
+ 	^ AtomicTypes at: 'uint64_t'!
- 	^ self unsignedLongLong!

Item was changed:
  ----- Method: ExternalType class>>uint8_t (in category 'type constants - stdint.h') -----
  uint8_t
  
+ 	^ AtomicTypes at: 'uint8_t'!
- 	^ self unsignedByte!

Item was changed:
  ----- Method: ExternalType class>>uintptr_t (in category 'type constants - stddef.h') -----
  uintptr_t
  	"Answer an unsigned integer type that can hold a data pointer on the current platform, that is, 4-byte pointers on 32-bit und 8-byte pointers on 64-bit. Unlike actual C pointers (e.g., void*), you can do (pointer) arithmetic (e.g., #+) and bitwise manipulation (e.g., #bitOr:) on the resulting Smalltalk Integer objects.
  	
  	Note that the equivalent type for a void* yields an instance if ExternalData, whose handle is an ExternalAddress, which actually impelements #+ as of June 2020. So, you can also do pointer arithmetic using that type.
  	
  	Note that all FFI calls and struct types will be updated automatically on startup if a platform change is detected."
  
  	^ FFIPlatformDescription current wordSize = 4
+ 		ifTrue: [self uint32_t]
+ 		ifFalse: [self uint64_t]!
- 		ifTrue: [self unsignedInt]
- 		ifFalse: [self unsignedLongLong]!

Item was changed:
  ----- Method: ExternalType class>>ulong (in category 'type constants') -----
  ulong
  
+ 	self flag: #deprecated.
+ 	^ self uint32_t!
- 	self flag: #ffiLongVsInt.
- 	^ self unsignedLong!

Item was changed:
  ----- Method: ExternalType class>>ulonglong (in category 'type constants') -----
  ulonglong
+ 
+ 	self flag: #deprecated.
+ 	^ self uint64_t!
- 	^ self unsignedLongLong!

Item was changed:
  ----- Method: ExternalType class>>unsignedByte (in category 'type constants') -----
  unsignedByte
+ 
+ 	self flag: #deprecated.
+ 	^ self uint8_t!
- 	^AtomicTypes at: 'byte'!

Item was changed:
  ----- Method: ExternalType class>>unsignedInt (in category 'type constants') -----
  unsignedInt
  
+ 	self flag: #deprecated.
+ 	^ self uint32_t!
- 	self flag: #ffiLongVsInt.
- 	^ self unsignedLong!

Item was changed:
  ----- Method: ExternalType class>>unsignedLong (in category 'type constants') -----
  unsignedLong
  
+ 	self flag: #deprecated.
+ 	^ self uint32_t!
- 	self flag: #ffiLongVsInt.
- 	^ AtomicTypes at: 'ulong'!

Item was changed:
  ----- Method: ExternalType class>>unsignedLongLong (in category 'type constants') -----
  unsignedLongLong
+ 	
+ 	self flag: #deprecated.
+ 	^ self uint64_t!
- 	^AtomicTypes at: 'ulonglong'!

Item was changed:
  ----- Method: ExternalType class>>unsignedShort (in category 'type constants') -----
  unsignedShort
+ 
+ 	self flag: #deprecated.
+ 	^ self uint16_t!
- 	^AtomicTypes at: 'ushort'!

Item was changed:
  ----- Method: ExternalType class>>ushort (in category 'type constants') -----
  ushort
+ 
+ 	self flag: #deprecated.
+ 	^ self uint16_t!
- 	^self unsignedShort!

Item was changed:
  ----- Method: ExternalType>>isIntegerType (in category 'testing - integer') -----
  isIntegerType
  	"Return true if the receiver is a built-in integer type"
  	| type |
  	type := self atomicType.
+ 	^type >= FFITypeUnsignedInt8 and:[type <= FFITypeSignedInt64]!
- 	^type > FFITypeBool and:[type <= FFITypeSignedLongLong]!

Item was changed:
+ (PackageInfo named: 'FFI-Kernel') postscript: '"Reinitialize new names and codes for atomic types."
+ FFIConstants initialize.
+ ExternalType resetAllTypes.'!
- (PackageInfo named: 'FFI-Kernel') postscript: '"Reinitialize FFIAtomicReadWriteSend to use the new integer primitives"
- ExternalType resetAllTypes...'!



More information about the Squeak-dev mailing list