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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 19 08:20:40 UTC 2021


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

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

Name: FFI-Kernel-mt.214
Author: mt
Time: 19 August 2021, 10:20:38.176627 am
UUID: 4bcee412-2de2-e54e-af6d-a252133d599d
Ancestors: FFI-Kernel-mt.213

Fixes start-up regression when moving 64-bit images between platforms. This is essentially a no-op now because we only have byte-alignment issues between 32-bit platforms. See ExternalAtomicType class >> #atomicTypeSpecs.

Simplify #reset* methods on ExternalType class. Also update its commentary. A RESET should only be done as a last resort when the image state is corrupt. For all normal cases, use #initialize. And you must not use FFI during the reset.

Removes obsolete #becomeStructureType method. ExternalUnknownType has all it needs.

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

Item was added:
+ ----- 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 .
+ 		#'uchar16_t'. 2 .         2 .
+ 		#'char16_t' . 2 .         2 .
+ 		#'uchar32_t'. 4 .         4 .
+ 		#'char32_t' . 4 .         4 .
+ 
+ 		#'float'    . 4 .         4 .
+ 		#'double'   . 8 .         isNonArm32BitUnix ifTrue: [4] ifFalse: [8] .
+ 	}!

Item was changed:
  ----- Method: ExternalAtomicType class>>initializeAtomicTypes (in category 'class initialization') -----
  initializeAtomicTypes
  	"Fill all known instances of the receiver with the correct state. See super implementation to learn about the entire initialization process."
  
- 	| atomicType byteSize type typeName byteAlignment |
  	self assert: [AtomicTypes notNil].
  	self assert: [AtomicTypes notEmpty].
  
+ 	self atomicTypeSpecs groupsDo: [:typeName :byteSize :byteAlignment |
+ 		| type typeCode compiled |
+ 				
- 	#(
- 		"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          8)
- 		(#'int64_t'   8          8)
- 
- 		(#'uchar8_t'  1          1)
- 		(#'char8_t'   1          1)
- 		(#'uchar16_t' 2          2)
- 		(#'char16_t'  2          2)
- 		(#'uchar32_t' 4          4)
- 		(#'char32_t'  4          4)
- 
- 		(#'float'     4          4)
- 		(#'double'    8          8)
- "TODO: ('longdouble' 10			16? 4?)"
- 	) do:[:typeSpec| | compiled |
- 		typeName := typeSpec first.
- 		byteSize := typeSpec second.
- 		byteAlignment := typeSpec third.
- 		
- 		"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: [
- 					byteAlignment := 4]].
- 		
  		"1) Regular type; put type code into headerWord"
  		type := AtomicTypes at: typeName.
+ 		typeCode := AtomicTypeCodes at: typeName.
- 		atomicType := AtomicTypeCodes at: typeName.
  		compiled := WordArray with: ((byteSize bitOr: FFIFlagAtomic) bitOr:
+ 				(typeCode bitShift: FFIAtomicTypeShift)).
- 				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: byteAlignment.
  		
  		"2) Pointer type; put type code into headerWord, too"
  		type := type asPointerType.
  		compiled := WordArray with: ((self pointerSpec bitOr: FFIFlagAtomic) bitOr:
+ 				(typeCode bitShift: FFIAtomicTypeShift)).
- 				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
+ 		type byteAlignment: self pointerAlignment].
+ 	
+ 	self noticeModificationOfAtomics.!
- 		type byteAlignment: self pointerAlignment.
- 	].!

Item was changed:
  ----- Method: ExternalStructure class>>defineAllChangedFields (in category 'system startup') -----
  defineAllChangedFields
  	"
  	ExternalStructure defineAllChangedFields
  	"
  	self allStructuresInCompilationOrder do: [:structClass |
  		structClass defineChangedFields.
  		structClass organization removeEmptyCategories].
+ 	
+ 	"No #cleanupUnusedTypes because this method must be fast. See ExternalType class >> #initializeFast."!
- 
- 	"Compilation of fields only needs external types temporarily. Non-weak references to external types are only in methods with FFI calls."
- 	ExternalType cleanupUnusedTypes.!

Item was removed:
- ----- Method: ExternalType class>>initializeArrayTypes (in category 'class initialization') -----
- initializeArrayTypes
- 	"Private. Initialize all array types that have an atomic-or-pointer type as their content type. Other array types will be updated through #initializeStructureTypes because of how #defineAllFields work with its callback to ExternalType class >> #noticeModificationOf:."
- 
- 	self allArrayTypesDo: [:arrayType |
- 		(arrayType contentType isAtomic or: [arrayType contentType isPointerType]) ifTrue: [
- 			arrayType newContentType: arrayType contentType]].!

Item was changed:
  ----- Method: ExternalType class>>initializeFast (in category 'class initialization') -----
  initializeFast
  	"Faster than #initialize. Update all atomic types for platform-specifc byte size and alignment. Also update struct and array types when they change due to changed atomics. NOTE THAT this cannot be used when atomic-type codes have changed!!"
  
  	ExternalAtomicType initializeAtomicTypes.
- 	self initializeArrayTypes.
  	ExternalStructure defineAllChangedFields.!

Item was changed:
  ----- Method: ExternalType class>>initializeStructureTypes (in category 'class initialization') -----
  initializeStructureTypes
  	"(Re-)initialize all structure types and all array types. Preserves object identity of all involved types. If the amount of types changed, use #resetAllStructureTypes instead."
  
  	self basicInitializeStructureTypes.
  	self invalidateStructureTypes.
+ 		
+ 	"Trigger #noticeModificationOf: callback to actually initialize all structure types. Since we invalidated all types, we cannot use #defineAllChangedFields. We rely on the #noticeModificationOf: callback."
+ 	ExternalStructure defineAllFields.!
- 	
- 	"1) Initialize all array types that have an atomic-or-pointer type as their content type."
- 	self initializeArrayTypes.
- 	
- 	"2) Trigger #noticeModificationOf: callback to actually initialize all structure types. Since we invalidated all types, we cannot use #defineAllChangedFields. We rely on the #noticeModificationOf: callback."
- 	ExternalStructure defineAllFields.
- 
- 	"Finally do some garbage collection."
- 	self cleanupUnusedTypes.!

Item was changed:
  ----- Method: ExternalType class>>invalidateStructureTypes (in category 'class initialization') -----
  invalidateStructureTypes
+ 	"Invalidate all types that will be updated through the #noticeModificationOf: callback when #defineFields or #defineAllFields is called."
  
+ 	self allAtomicTypesDo: [:atomicType |
+ 		atomicType referentClass ifNotNil: [ "i.e., alias-to-atomic"
+ 			atomicType "asNonPointerType" invalidate.
+ 			atomicType asPointerType invalidate]].
+ 	
+ 	self allArrayTypesDo: [:arrayType |
+ 		arrayType contentType referentClass ifNotNil: [ "i.e., not a genuine array-of-atomics"
+ 			arrayType "asNonPointerType" invalidate.
+ 			arrayType asPointerType invalidate]].
- 	self typeAliasTypesDo: [:type | type isAtomic ifTrue: [
- 		type "asNonPointerType" invalidate.
- 		type asPointerType invalidate]].
  
  	self allStructTypesDo:[:structType |
  		structType "asNonPointerType" invalidate.
+ 		structType asPointerType invalidate].!
- 		structType asPointerType invalidate].
- 	
- 	self allArrayTypesDo: [:arrayType |
- 		arrayType "asNonPointerType" invalidate.
- 		arrayType asPointerType invalidate].!

Item was added:
+ ----- Method: ExternalType class>>noticeModificationOfAtomics (in category 'housekeeping') -----
+ noticeModificationOfAtomics
+ 	"Atomic types have been redefined. Initialize all array types that have an atomic-or-pointer type as their content type. Other array types will be updated through #initializeStructureTypes because of how #defineAllFields work with its callback to ExternalType class >> #noticeModificationOf:."
+ 
+ 	ArrayTypes ifNil: [^ self "Not yet initialized"].
+ 	self arrayTypesDo: [:arrayType |
+ 		(arrayType contentType isAtomic or: [arrayType contentType isPointerType]) ifTrue: [
+ 			arrayType newContentType: arrayType contentType]].!

Item was changed:
  ----- Method: ExternalType class>>platformChangedFrom:to: (in category 'system startup') -----
  platformChangedFrom: lastPlatform to: currentPlatform
  	"Byte size or byte alignment for atomic types might be different on the new platform."
  	
+ 	lastPlatform pluginVersion ~= currentPlatform pluginVersion
+ 		ifTrue: ["Type codes might have changed. Re-init thoroughly. Preserve type identity."
+ 			self initialize "Slower but necessary for new type codes"]
+ 		ifFalse: ["Byte alignment of double and int64_t might have changed. Re-init quickly. Preserve type identity."
+ 			currentPlatform wordSize = 4 ifTrue: [self initializeFast]].
- 	lastPlatform pluginVersion = currentPlatform pluginVersion
- 		ifTrue: [self initializeFast]
- 		ifFalse: [self initialize "Slower but necessary for new type codes"].
  	
  	self flag: #todo. "mt: Update all critical aliases for atomic types, i.e., intptr_t, uintptr_t. But what about 'c_long' between 64-bit platforms?!!"
  	"lastPlatform wordSize ~= currentPlatform wordSize
  		ifTrue: [self recompileAllLibraryFunctions]."!

Item was removed:
- ----- Method: ExternalType class>>resetAllArrayClasses (in category 'housekeeping') -----
- resetAllArrayClasses
- 
- 	ArrayClasses := nil.
- 	self initializeArrayClasses.!

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

Item was removed:
- ----- Method: ExternalType class>>resetAllStructureTypes (in category 'housekeeping') -----
- resetAllStructureTypes
- 	"Warning: This call is only required if you change the container for StructTypes!! Note that (2) and (3) can be swapped but that puts unnecessary pressure on the GC."
- 
- 	StructTypes := nil.
- 	ArrayTypes := nil.
- 	
- 	"1) Initialize the container for structure types."
- 	self initializeStructureTypes.
- 	
- 	"2) Trigger #noticeModificationOf: callback to actually initialize all structure types."
- 	ExternalTypePool reset.
- 	ExternalStructure defineAllFields. "Even if unchanged, we need to fill the type pool."
- 	ExternalTypePool cleanUp.
- 
- 	"3) Recompile all FFI calls to create and persist structure types."
- 	self recompileAllLibraryFunctions.
- 	
- 	"4) Just in case, we also lookup available array classes. Maybe we have one for a specific struct type, right? :-)"
- 	self resetAllArrayClasses.
- !

Item was changed:
  ----- Method: ExternalType class>>resetAllTypes (in category 'housekeeping') -----
  resetAllTypes
+ 	"DANGEROUS!! Only do this if you think that your image is in an inconsistent state. You must not actively use FFI (i.e., have instances of external structures or external data) while calling this."
- 	"If we reset the atomic types, we reset everything else."
  	
+ 	ExternalTypePool nukeAll.
+ 
+ 	AtomicTypeCodes := nil.
+ 	AtomicTypes := nil.
+ 	StructTypes := nil.
+ 	ArrayTypes := nil.
+ 	ArrayClasses := nil.
+ 
+ 	self initialize.
+ 	self recompileAllLibraryFunctions.!
- 	self resetAllAtomicTypes.!

Item was removed:
- ----- Method: ExternalType>>becomeStructureType (in category 'private - type alias') -----
- becomeStructureType
- 
- 	self class = ExternalStructure ifTrue: [^ self].
- 
- 	self class = ExternalPointerType ifTrue: [		
- 		| newPointerType |
- 		"We are not a type alias for a pointer type anymore."
- 		self changeClassTo: ExternalStructureType.
- 
- 		"Fetch my updated spec as a structure type."
- 		compiledSpec := referentClass compiledSpec.
- 		byteAlignment := referentClass byteAlignment.
- 		
- 		"Prepare and set my new, dedicated pointer type."
- 		(newPointerType := ExternalPointerType basicNew)
- 			compiledSpec: (WordArray with: self class pointerSpec);
- 			byteAlignment: self class pointerAlignment;
- 			setReferentClass: referentClass;
- 			setReferencedType: self.
- 		referencedType := newPointerType. 
- 
- 		"Done. Answer self because of #changeClassTo:."
- 		^ self].
- 	
- 	self class = ExternalArrayType ifTrue: [
- 		"An not #isTypeAliasForArray anymore. :-( "
- 		| newStructType |
- 		newStructType := ExternalStructureType basicNew
- 			compiledSpec: self compiledSpec;
- 			byteAlignment: self byteAlignment;
- 			setReferentClass: referentClass;
- 			setReferencedType: referencedType;
- 			yourself.
- 			
- 		"Not a pointer type for array type anymore."
- 		referencedType setReferentClass: referentClass.
- 		
- 		self becomeForward: newStructType.
- 		self assert: [newStructType class = ExternalStructureType].
- 		^ newStructType].!



More information about the Squeak-dev mailing list