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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 16 09:45:05 UTC 2021


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

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

Name: FFI-Kernel-mt.220
Author: mt
Time: 16 September 2021, 11:45:03.11532 am
UUID: 775f007d-57d5-5a48-926b-4570ea27b939
Ancestors: FFI-Kernel-mt.219

No signed character types anymore. "char" and "uchar" (and "schar") have all the same type codes for the plugin.

Avoid dependency on type codes in #isCharType and #isIntegerType and #isSigned to support different plugin versions.

Minor fix in #initializeAtomicTypeCodes when removing (un-aliased) atomic type names (here: char8_t, char16_t, char32_t -- these are now aliases for uchar8_t, uchar16_t, uchar32_t).

=============== Diff against FFI-Kernel-mt.219 ===============

Item was changed:
  ----- Method: CharacterReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: type
  
+ 	^ super fromType: type asIntegerType!
- 	^ super fromType: ExternalType byte!

Item was changed:
  ----- Method: ExternalAtomicType class>>atomicTypeSpecs (in category 'class initialization') -----
  atomicTypeSpecs
  
  	| platform isNonArm32BitUnix |
  	platform := FFIPlatformDescription current.
  	isNonArm32BitUnix := platform wordSize = 4 and: [platform isUnix and: [platform isARM not]].
  	^ {
  		"name         byte size   byte alignment"
  		#'void'     . 0 .         0 . "No non-pointer support in calls. Duh. ;-)"
  		#'bool'     . 1 .         1 . "No pointer support in calls."
  
  		#'uint8_t'  . 1 .         1 .
  		#'int8_t'   . 1 .         1 .
  		#'uint16_t' . 2 .         2 .
  		#'int16_t'  . 2 .         2 .
  		#'uint32_t' . 4 .         4 .
  		#'int32_t'  . 4 .         4 .
  		#'uint64_t' . 8 .         isNonArm32BitUnix ifTrue: [4] ifFalse: [8] .
  		#'int64_t'  . 8 .         isNonArm32BitUnix ifTrue: [4] ifFalse: [8] .
  
  		#'uchar8_t' . 1 .         1 .
+ 		"#'char8_t'  . 1 .         1 ."
- 		#'char8_t'  . 1 .         1 .
  		#'uchar16_t'. 2 .         2 .
- 		#'char16_t' . 2 .         2 .
  		#'uchar32_t'. 4 .         4 .
- 		#'char32_t' . 4 .         4 .
  
+ 		"#'half'     . 2 .         2 ."
  		#'float'    . 4 .         4 .
  		#'double'   . 8 .         isNonArm32BitUnix ifTrue: [4] ifFalse: [8] .
  	}!

Item was changed:
  ----- Method: ExternalAtomicType class>>initializeAtomicTypeCompanions (in category 'class initialization') -----
  initializeAtomicTypeCompanions
  
  	#(
  		"name         companion"
  		(#'void'      nil)
  		(#'bool'      nil)
  
  		(#'uint8_t'   #'int8_t')
  		(#'int8_t'    #'uint8_t')
  		(#'uint16_t'  #'int16_t')
  		(#'int16_t'   #'uint16_t')
  		(#'uint32_t'  #'int32_t')
  		(#'int32_t'   #'uint32_t')
  		(#'uint64_t'  #'int64_t')
  		(#'int64_t'   #'uint64_t')
  
+ 		(#'uchar8_t'      nil)
+ 		(#'uchar16_t'      nil)
+ 		(#'uchar32_t'      nil)
- 		(#'uchar8_t'  #'char8_t')
- 		(#'char8_t'   #'uchar8_t')
- 		(#'uchar16_t' #'char16_t')
- 		(#'char16_t'  #'uchar16_t')
- 		(#'uchar32_t' #'char32_t')
- 		(#'char32_t'  #'uchar32_t')
  
  		(#'float'     #'double')
  		(#'double'    #'float')
  
  	) do:[:spec| | type companion |
  		type := ExternalType typeNamed: spec first.
  		companion := spec second ifNotNil: [ExternalType typeNamed: spec second].
  		type setCompanionType: companion.
  		companion ifNotNil: [companion setCompanionType: type]].!

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

Item was added:
+ ----- Method: ExternalType class>>char16_t (in category 'type constants') -----
+ char16_t
+ 
+ 	^ self uchar16_t!

Item was added:
+ ----- Method: ExternalType class>>char32_t (in category 'type constants') -----
+ char32_t
+ 
+ 	^ self uchar32_t!

Item was added:
+ ----- Method: ExternalType class>>char8_t (in category 'type constants') -----
+ char8_t
+ 
+ 	^ self uchar8_t!

Item was changed:
  ----- Method: ExternalType class>>initializeAtomicTypeCodes (in category 'class initialization') -----
  initializeAtomicTypeCodes
  	"ExternalType initializeAtomicTypeCodes"
  
  	FFIConstants initialize. "Init appropriate type codes for current plugin version."
  
  	AtomicTypeCodes := OrderedDictionary newFrom: {
  		#'void' -> FFITypeVoid.
  		#'bool' -> FFITypeBool.
  		
  		#'uint8_t' -> FFITypeUnsignedInt8.
  		#'int8_t' -> FFITypeSignedInt8.
  		#'uint16_t' -> FFITypeUnsignedInt16.
  		#'int16_t' -> FFITypeSignedInt16.
  		#'uint32_t' -> FFITypeUnsignedInt32.
  		#'int32_t' -> FFITypeSignedInt32.
  		#'uint64_t' -> FFITypeUnsignedInt64.
  		#'int64_t' -> FFITypeSignedInt64.
  		
  		#'uchar8_t' -> FFITypeUnsignedChar8.
+ 		"#'char8_t' -> FFITypeSignedChar8."
- 		#'char8_t' -> FFITypeSignedChar8.
  		#'uchar16_t' -> FFITypeUnsignedChar16.
- 		#'char16_t' -> FFITypeSignedChar16.
  		#'uchar32_t' -> FFITypeUnsignedChar32.
- 		#'char32_t' -> FFITypeSignedChar32.
  		
  		#'float' -> FFITypeSingleFloat.
  		#'double' -> FFITypeDoubleFloat}.
  	
  	"We must now update the names of all known atomic types."
  	AtomicTypes ifNotNil: [
  		AtomicTypes keys do: [:oldName |
  			| type newName |
  			type := AtomicTypes at: oldName.
+ 			newName := AtomicTypeCodes keyAtValue: type atomicType ifAbsent: [oldName].
- 			newName := AtomicTypeCodes keyAtValue: type atomicType.
  			(AtomicTypes includesKey: newName) ifFalse: [
  				"Only store new names. Do not support name swap."
  				AtomicTypes removeKey: oldName.
  				AtomicTypes at: newName put: type.
  				type setAtomicTypeName: newName]]].!

Item was changed:
  ----- Method: ExternalType>>asCharType (in category 'converting - integer / char') -----
  asCharType
  	"When the receiver is an integer type, answer the corresponding character type."
  	
  	self isCharType ifTrue: [^ self].
  	self isIntegerType ifFalse: [^ self error: 'Cannot convert non-integer type to char type'].
  	
+ 	self byteSize = 1 ifTrue: [^ self class uchar8_t].
+ 	self byteSize = 2 ifTrue: [^ self class uchar16_t].
+ 	self byteSize = 4 ifTrue: [^ self class uchar32_t].
- 	self byteSize = 1 ifTrue: [^ self isSigned ifTrue: [self class char8_t] ifFalse: [self class uchar8_t]].
- 	self byteSize = 2 ifTrue: [^ self isSigned ifTrue: [self class char16_t] ifFalse: [self class uchar16_t]].
- 	self byteSize = 4 ifTrue: [^ self isSigned ifTrue: [self class char32_t] ifFalse: [self class uchar32_t]].
  
  	self error: 'Cannot convert integer to char type; unsupported byteSize'.!

Item was changed:
  ----- Method: ExternalType>>asIntegerType (in category 'converting - integer / char') -----
  asIntegerType
  	"When the receiver is a character type, answer the corresponding integer type."
  
  	self isIntegerType ifTrue: [^ self].
  	self isCharType ifFalse: [^ self error: 'Cannot convert non-char type to integer type'].
  	
+ 	self byteSize = 1 ifTrue: [^ self class uint8_t].
+ 	self byteSize = 2 ifTrue: [^ self class uint16_t].
+ 	self byteSize = 4 ifTrue: [^ self class uint32_t].
- 	self byteSize = 1 ifTrue: [^ self isSigned ifTrue: [self class int8_t] ifFalse: [self class uint8_t]].
- 	self byteSize = 2 ifTrue: [^ self isSigned ifTrue: [self class int16_t] ifFalse: [self class uint16_t]].
- 	self byteSize = 4 ifTrue: [^ self isSigned ifTrue: [self class int32_t] ifFalse: [self class uint32_t]].
  
  	self error: 'Cannot convert char to integer type; unsupported byteSize'.!

Item was changed:
  ----- Method: ExternalType>>checkIntegerType (in category 'private') -----
  checkIntegerType
  
+ 	self isIntegerType
- 	(self isIntegerType or: [self isCharType])
  		ifFalse: [self error: 'Test is only defined on integer types!!'].!

Item was changed:
  ----- Method: ExternalType>>isCharType (in category 'testing - integer / char') -----
  isCharType
+ 	"Return true if the receiver is a built-in character type. Note that we want to avoid hard-coding type codes and invariants around type codes here to remain compatible with different plugin versions."
+ 
- 	
  	| type |
  	type := self atomicType.
+ 	type = FFITypeUnsignedChar8 ifTrue: [^ true].
+ 	type = FFITypeSignedChar8 ifTrue: [^ true].
+ 	type = FFITypeUnsignedChar16 ifTrue: [^ true].
+ 	type = FFITypeUnsignedChar32 ifTrue: [^ true].
+ 	^ false!
- 	^ type >= FFITypeUnsignedChar8 and: [type <= FFITypeSignedChar32]!

Item was changed:
  ----- Method: ExternalType>>isIntegerType (in category 'testing - integer / char') -----
  isIntegerType
+ 	"Return true if the receiver is a built-in integer type. Note that we want to avoid hard-coding type codes and invariants around type codes here to remain compatible with different plugin versions."
+ 
- 	"Return true if the receiver is a built-in integer type"
  	| type |
  	type := self atomicType.
+ 	type = FFITypeUnsignedInt8 ifTrue: [^ true].
+ 	type = FFITypeSignedInt8 ifTrue: [^ true].
+ 	type = FFITypeUnsignedInt16 ifTrue: [^ true].
+ 	type = FFITypeSignedInt16 ifTrue: [^ true].
+ 	type = FFITypeUnsignedInt32 ifTrue: [^ true].
+ 	type = FFITypeSignedInt32 ifTrue: [^ true].
+ 	type = FFITypeUnsignedInt64 ifTrue: [^ true].
+ 	type = FFITypeSignedInt64 ifTrue: [^ true].
+ 	^ false!
- 	^type >= FFITypeUnsignedInt8 and:[type <= FFITypeSignedInt64]!

Item was changed:
  ----- Method: ExternalType>>isSigned (in category 'testing - integer / char') -----
  isSigned
+ 	"Return true if the receiver is a signed integer type. Note that we want to avoid hard-coding type codes and invariants around type codes here to remain compatible with different plugin versions."
- 	"Return true if the receiver is a signed integer type."
  
+ 	| type |
+ 	type := self atomicType.
+ 	type = FFITypeSignedInt8 ifTrue: [^ true].
+ 	type = FFITypeSignedInt16 ifTrue: [^ true].
+ 	type = FFITypeSignedInt32 ifTrue: [^ true].
+ 	type = FFITypeSignedInt64 ifTrue: [^ true].
  	self checkIntegerType.
+ 	^ false!
- 	^self atomicType anyMask: 1!

Item was changed:
+ (PackageInfo named: 'FFI-Kernel') postscript: '"Update for array classes. No type codes for signed char types anymore."
+ ExternalType initialize...'!
- (PackageInfo named: 'FFI-Kernel') postscript: '"Update for array classes."
- ExternalType initialize..'!



More information about the Squeak-dev mailing list