[squeak-dev] FFI: FFI-Tests-mt.61.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 17 10:30:22 UTC 2021


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

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

Name: FFI-Tests-mt.61
Author: mt
Time: 17 August 2021, 12:30:22.330505 pm
UUID: d92ebf12-e21a-1646-b151-10aa59cfc878
Ancestors: FFI-Tests-mt.60

Complements FFI-Kernel-mt.208

=============== Diff against FFI-Tests-mt.60 ===============

Item was changed:
  ----- Method: ExternalTypeTests>>testAllArrayTypes (in category 'tests - image') -----
  testAllArrayTypes
  
+ 	ExternalType allArrayTypes do: [:type |
- 	ExternalType arrayTypes do: [:type |
  		self
  			deny: type isAtomic;
  			deny: type isPointerType;
  			deny: type isStructureType;
  			assert: type isArrayType].!

Item was changed:
  ----- Method: ExternalTypeTests>>testAllAtomicTypes (in category 'tests - image') -----
  testAllAtomicTypes
  
+ 	ExternalType allAtomicTypes do: [:type |
- 	ExternalType atomicTypes do: [:type |
  		self
  			assert: type isAtomic;
  			deny: type isPointerType;
  			deny: type isStructureType;
+ 			deny: type isArrayType].!
- 			deny: type isArrayType;
- 			deny: type isTypeAlias].!

Item was changed:
  ----- Method: ExternalTypeTests>>testAllPointerTypes (in category 'tests - image') -----
  testAllPointerTypes
  
+ 	ExternalType allPointerTypes do: [:type |
- 	ExternalType pointerTypes do: [:type |
  		self
  			deny: type isAtomic;
  			assert: type isPointerType;
  			deny: type isStructureType;
  			deny: type isArrayType].!

Item was changed:
  ----- Method: ExternalTypeTests>>testAllStructureTypes (in category 'tests - image') -----
  testAllStructureTypes
  
+ 	ExternalType allStructTypes do: [:type |
- 	ExternalType structTypes do: [:type |
  		self
  			deny: type isAtomic;
  			deny: type isPointerType;
  			assert: type isStructureType;
  			deny: type isArrayType].!

Item was changed:
  ----- Method: ExternalTypeTests>>testAtomicTypeRange (in category 'tests - atomic types') -----
  testAtomicTypeRange
  	"Tests the range of non-integer and non-float types. Includes char types because those look different in Smalltalk."
  	
  	self should: [ExternalType void minVal] raise: Error.
  	self should: [ExternalType void maxVal] raise: Error.
  
  	self should: [ExternalType bool minVal] raise: Error.
  	self should: [ExternalType bool maxVal] raise: Error.	
  
+ 	self should: [ExternalType char8_t minVal] raise: Error.
+ 	self should: [ExternalType char8_t maxVal] raise: Error.	
- 	self should: [ExternalType char "unsignedChar" minVal] raise: Error.
- 	self should: [ExternalType char "unsignedChar" maxVal] raise: Error.	
  
+ 	self should: [ExternalType uchar8_t minVal] raise: Error.
+ 	self should: [ExternalType uchar8_t maxVal] raise: Error.	
- 	self should: [ExternalType signedChar "schar" minVal] raise: Error.
- 	self should: [ExternalType signedChar "schar" maxVal] raise: Error.	
  !

Item was changed:
  ----- Method: ExternalTypeTests>>testFloatTypes (in category 'tests - atomic float types') -----
  testFloatTypes
  
  	#(
  		float 4
  		double 8
  	) pairsDo: [:typeName :byteSize |
  		| type |
  		type := ExternalType typeNamed: typeName.
  		self
  			assert: type isFloatType;
+ 			assert: byteSize equals: type byteSize;
+ 			assert: type companionType notNil;
+ 			assert: type companionType isFloatType].!
- 			assert: byteSize equals: type byteSize].!

Item was changed:
  ----- Method: ExternalTypeTests>>testIntegerTypes (in category 'tests - atomic integer types') -----
  testIntegerTypes
  
  	#(
  		uint8_t 1 int8_t 1
  		uint16_t 2 int16_t 2
  		uint32_t 4 int32_t 4
  		uint64_t 8 int64_t 8
  	) pairsDo: [:typeName :byteSize |
  		| type |
  		type := ExternalType typeNamed: typeName.
  		self
  			assert: type isIntegerType;
+ 			assert: byteSize equals: type byteSize;
+ 			assert: type companionType notNil;
+ 			assert: type companionType isIntegerType].!
- 			assert: byteSize equals: type byteSize].!

Item was added:
+ ----- Method: ExternalTypeTests>>testIntegerTypesAsCharTypes (in category 'tests - atomic integer types') -----
+ testIntegerTypesAsCharTypes
+ 
+ 	#( int8_t int16_t int32_t ) do: [:typeName |
+ 		| integerType |
+ 		integerType := ExternalType typeNamed: typeName.
+ 		self
+ 			assert: integerType isSigned;
+ 			assert: integerType asCharType isCharType;
+ 			assert: integerType byteSize equals: integerType asCharType byteSize;
+ 			assert: integerType isSigned equals: integerType asCharType isSigned;
+ 			
+ 			assert: integerType asUnsigned isUnsigned;
+ 			assert: integerType asUnsigned asCharType isCharType;
+ 			assert: integerType asUnsigned byteSize equals: integerType asUnsigned asCharType byteSize;
+ 			assert: integerType asUnsigned isUnsigned equals: integerType asUnsigned asCharType isUnsigned].!

Item was changed:
  ----- Method: ExternalTypeTests>>testPointerToPointerVsArrayOfPointers (in category 'tests - pointer types') -----
  testPointerToPointerVsArrayOfPointers
  	"For visual clarity, the pointer type of an array-of-pointers type will look different from the pointer type of an array-of-atomics/structs. Also see #testPointerToPointer."
  
  	| arrayType |
+ 	arrayType := ExternalType typeNamed: 'int32_t[]'.
- 	arrayType := ExternalType typeNamed: 'char[]'.
  	
  	self
+ 		assert: '(int32_t[])*'
- 		assert: '(char[])*'
  		equals: arrayType asPointerType typeName.
  		
+ 	arrayType := ExternalType typeNamed: 'int32_t*[]'.
- 	arrayType := ExternalType typeNamed: 'char*[]'.
  	
  	self
+ 		assert: '(int32_t*[])*'
- 		assert: '(char*[])*'
  		equals: arrayType asPointerType typeName.!

Item was changed:
  ----- Method: FFIAllocateTests>>test10ArrayClasses (in category 'tests - array') -----
  test10ArrayClasses
  	"For integer and float types, allocate arrays and check for specific array classes. Then construct a conventional byte array for an external data structure. A copy should also convert into a specific array class with the same contents."
  	
  	ExternalType useArrayClassesDuring: [
  		
  	ExternalType atomicTypes do: [:contentType |
  		(contentType isIntegerType
  			or: [contentType isFloatType]
+ 			or: [contentType isCharType and: [contentType byteSize ~= 2 "No array class for 16-bit characters yet"]]) ifTrue: [
- 			or: [contentType isCharType]) ifTrue: [
  				| array arrayType data copy |
  				array := self allocate: contentType size: 5.
  				arrayType := array externalType.
  
  				self assert: array isFFIArray.
  				self assert: 5 equals: array size.
  				self assert: array byteSize equals: arrayType byteSize.
  				
+ 				contentType isCharType ifFalse: [
- 				contentType = ExternalType signedChar ifFalse: [
  					self flag: #discuss. "mt: What is signedChar even for?"
  					self assert: contentType equals: array contentType].
  
  				self deny: array isNull.
  				self deny: (array isKindOf: ExternalData).
  				self assert: array equals: array getHandle.
  				
  				self shouldnt: [array at: 1 put: contentType allocate first] raise: Error.
  				self shouldnt: [array zeroMemory] raise: Error.
  				self should: [array setContentType: ExternalType byte] raise: Error.
  				self should: [array setSize: 42] raise: Error.
  
  				data := ExternalData
  					fromHandle: (ByteArray new: arrayType byteSize)
  					type: arrayType.
  				copy := data copy. "From external data into raw-bits array."
  				self deny: array equals: data.			
  				self assert: array equals: copy. ]]].!



More information about the Squeak-dev mailing list