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

commits at source.squeak.org commits at source.squeak.org
Sun May 23 13:45:10 UTC 2021


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

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

Name: FFI-Kernel-mt.167
Author: mt
Time: 23 May 2021, 3:45:09.673158 pm
UUID: 6e67015a-9732-e741-aefe-49f7cf42ef82
Ancestors: FFI-Kernel-mt.166

Complements FFI-Pools-mt.27. New preference for using a type pool for about 2x faster access to struct fields.

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

Item was changed:
  ----- Method: ByteArray>>structAt:length: (in category '*FFI-Kernel') -----
  structAt: byteOffset length: length
  	"Return a structure of the given length starting at the indicated byte offset."
  	
  	| value startByteOffset |
+ 	self flag: #todo. "mt: Better name #unsignedBytesAt:length:?"
  	value := ByteArray new: length.
  	startByteOffset := byteOffset - 1.
  	1 to: length do: [:valueByteOffset |
  		value
  			unsignedByteAt: valueByteOffset
  			put: (self unsignedByteAt: startByteOffset + valueByteOffset)].
  	^ value!

Item was changed:
  ----- Method: ByteArray>>structAt:put:length: (in category '*FFI-Kernel') -----
  structAt: byteOffset put: value length: length
  	"Store a structure of the given length starting at the indicated byte offset."
  	
  	| startByteOffset |
+ 	self flag: #todo. "mt: Better name #unsignedBytesAt:put:length:?"
  	startByteOffset := byteOffset - 1.
  	1 to: length do: [:valueByteOffset |
  		self
  			unsignedByteAt: startByteOffset + valueByteOffset
  			put: (value unsignedByteAt:valueByteOffset)].
  	^ value!

Item was changed:
  ----- Method: ExternalArrayType>>readAlias (in category 'external structure') -----
  readAlias
  
  	^ '^ {1} fromHandle: handle{2}'
  		format: {
  			(referentClass ifNil: [ExternalData]) name.
  			referentClass ifNotNil: [''] ifNil: [
+ 				' type: ', self storeStringForField]}!
- 				' type: ', self storeString]}!

Item was changed:
  ----- Method: ExternalArrayType>>readFieldAt: (in category 'external structure') -----
  readFieldAt: byteOffset
  
  	^ '^ ExternalData fromHandle: (handle structAt: {1} length: {2}) type: {3}'
  		format: {
  			byteOffset.
  			self byteSize.
+ 			self storeStringForField}!
- 			self storeString}!

Item was changed:
  ----- Method: ExternalPointerType>>readFieldAt: (in category 'external structure') -----
  readFieldAt: byteOffset
  	"
  	ExternalStructure defineAllFields.
  	"
  	^ '^ {1} fromHandle: (handle pointerAt: {2} length: {3}){4}'
  		format: {
  			(referentClass ifNil: [ExternalData]) name.
  			byteOffset.
  			self byteSize.
  			referentClass ifNotNil: [''] ifNil: [
+ 				' type: ', self asNonPointerType "content type" storeStringForField]}!
- 				' type: ', self asNonPointerType "content type" storeString]}!

Item was changed:
  ExternalObject subclass: #ExternalStructure
  	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: 'ExternalTypePool FFIConstants'
- 	classVariableNames: 'PreviousPlatform'
- 	poolDictionaries: 'FFIConstants'
  	category: 'FFI-Kernel'!
  ExternalStructure class
  	instanceVariableNames: 'compiledSpec byteAlignment'!
  
  !ExternalStructure commentStamp: 'eem 6/26/2019 15:26' prior: 0!
  An ExternalStructure is for representing external data that is
  - either a structure composed of different fields (a struct of C language)
  - or an alias for another type (like a typedef of C language)
  
  It reserves enough bytes of data for representing all the fields.
  
  The data is stored into the handle instance variable which can be of two different types:
  	- ExternalAddress
  		If the handle is an external address then the object described does not reside in the Smalltalk object memory.
  	- ByteArray
  		If the handle is a byte array then the object described resides in Smalltalk memory.
  
  
  Instance Variables (class side)
  	byteAlignment:		<Integer>
  	compiledSpec:		<WordArray>
  
  byteAlignment
  	- the required alignment for the structure
  
  compiledSpec
  	- the bit-field definiton of the structure in the ExternalType encoding understood by the VM's FFI call marshalling machinery.
  
  
  A specific structure is defined by subclassing ExternalStructure and specifying its #fields via a class side method.
  For example if we define a subclass:
  	ExternalStructure subclass: #StructExample
  		instanceVariableNames: ''
  		classVariableNames: ''
  		poolDictionaries: ''
  		category: 'garbage'.
  Then declare the fields like this:
      StructExample class compile: 'fields  ^#( (name ''char*'') (color ''ulong'') )' classified: 'garbage'.
  
  It means that this type is composed of two different fields:
  - a string (accessed thru the field #name)
  - and an unsigned 32bit integer (accessed thru the field #color).
  It represents the following C type:
     struct StructExample {char *name; uint32_t color; };
  
  The accessors for those fields can be generated automatically like this:
  	StructExample defineFields.
  As can be verified in a Browser:
  	StructExample browse.
  We see that name and color fields are stored sequentially in different zones of data.
  
  The total size of the structure can be verified with:
  	StructExample byteSize = (Smalltalk wordSize + 4).
  
  An ExternalStructure can also be used for defining an alias.
  The fields definition must contain only 2 elements: an eventual accessor (or nil) and the type.
  For example, We can define a machine dependent 'unsigned long' like this:
  	ExternalStructure subclass: #UnsignedLong
  		instanceVariableNames: ''
  		classVariableNames: ''
  		poolDictionaries: ''
  		category: 'garbage'.
  Then set the fields like this:
      UnsignedLong class compile: 'fields  ^(Smalltalk wordSize=4 or: [Smalltalk platformName=''Win64''])
  		ifTrue: [#(nil ''ulong'')] ifFalse: [#(nil ''ulonglong'')]' classified: 'garbage'.
  And verify the size on current platform:
  	UnsignedLong byteSize.
  	
  Then, the class names 'UnsignedLong' and 'StructExamples' acts as a type specification.
  They can be used for composing other types, and for defining prototype of external functions:
  
  LibraryExample>>initMyStruct: aStructExample name: name color: anInteger
  	<cdecl: void 'init_my_struct'( StructExample * char * UnsignedLong )>
  	self externalCallFailed
  
  
  !
  ExternalStructure class
  	instanceVariableNames: 'compiledSpec byteAlignment'!

Item was changed:
  Object subclass: #ExternalType
  	instanceVariableNames: 'compiledSpec referentClass referencedType byteAlignment'
+ 	classVariableNames: 'ArrayClasses ArrayTypes AtomicSends AtomicTypeNames AtomicTypes ExtraTypeChecks StructTypes UseArrayClasses UseTypePool'
- 	classVariableNames: 'ArrayClasses ArrayTypes AtomicSends AtomicTypeNames AtomicTypes ExtraTypeChecks StructTypes UseArrayClasses'
  	poolDictionaries: 'FFIConstants'
  	category: 'FFI-Kernel'!
  
  !ExternalType commentStamp: 'mt 6/5/2020 18:25' prior: 0!
  An external type represents the type of external objects.
  
  Instance variables:
  	compiledSpec	<WordArray>		Compiled specification of the external type
  	referentClass	<Behavior | nil>	Class type of argument required
  	referencedType	<ExternalType>	Associated (non)pointer type with the receiver
  	byteAlignment	<Integer | nil>		The desired alignment for a field of the external type within a structure.  If nil it has yet to be computed.
  
  Compiled Spec:
  The compiled spec defines the type in terms which are understood by the VM. Each word is defined as:
  	bits 0...15 	- byte size of the entity
  	bit 16		- structure flag (FFIFlagStructure)
  				  This flag is set if the following words define a structure
  	bit 17		- pointer flag (FFIFlagPointer)
  				  This flag is set if the entity represents a pointer to another object
  	bit 18		- atomic flag (FFIFlagAtomic)
  				  This flag is set if the entity represents an atomic type.
  				  If the flag is set the atomic type bits are valid.
  	bits 19...23	- unused
  	bits 24...27	- atomic type (FFITypeVoid ... FFITypeDoubleFloat)
  	bits 28...31	- unused
  
  Note that all combinations of the flags FFIFlagPointer, FFIFlagAtomic, and FFIFlagStructure are invalid, EXCEPT from the following:
  
  	FFIFlagPointer + FFIFlagAtomic:
  		This defines a pointer to an atomic type (e.g., 'char*', 'int*').
  		The actual atomic type is represented in the atomic type bits.
  
  	FFIFlagPointer + FFIFlagStructure:
  		This defines a structure which is a typedef of a pointer type as in
  			typedef void* VoidPointer;
  			typedef Pixmap* PixmapPtr;
  		It requires a byte size of four or eight (e.g. a 32-bit or 64-bit pointer) to work correctly.
  
  [Note: Other combinations may be allowed in the future]
  !

Item was changed:
  ----- Method: ExternalType class>>resetAllAtomicTypes (in category 'housekeeping') -----
  resetAllAtomicTypes
  	"Warning: This call is only required if you change the initialization for AtomicTypes."
  
  	AtomicTypes := nil.
  	AtomicSends := nil.
+ 	ArrayClasses := nil.
+ 	
  	StructTypes := nil.
  	ArrayTypes := nil.
- 	ArrayClasses := nil.
  	
  	self initializeDefaultTypes.
  	self initializeArrayClasses.
  	self resetAllStructureTypes.!

Item was changed:
  ----- 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) Recompile all FFI calls to create and persist structure types."
  	self recompileAllLibraryFunctions.
  	
  	"3) Update all structure types' spec and alignment."
+ 	ExternalTypePool reset.
+ 	ExternalStructure defineAllFields.
+ 	ExternalTypePool cleanUp.
- 	ExternalStructure compileAllFields.
  !

Item was changed:
  ----- Method: ExternalType class>>useArrayClasses (in category 'preferences') -----
  useArrayClasses
+ 	<preference: 'Use array classes (i.e. RawBitsArray)'
- 	<preference: 'Use Array Classes (i.e. RawBitsArray)'
  		categoryList: #('FFI Kernel')
  		description: 'When true, type-based allocation in (local) object memory will use array classes instead of a ByteArray wrapped in ExternalData. Does not apply to external allocation.'
  		type: #Boolean>
  	^UseArrayClasses ifNil:[true]!

Item was added:
+ ----- Method: ExternalType class>>useTypePool (in category 'preferences') -----
+ useTypePool
+ 	<preference: 'Use type pool in structure fields'
+ 		categoryList: #('FFI Kernel')
+ 		description: 'When true, fill a pool of external types to be used in struct-field accessors. See ExternalTypePool.'
+ 		type: #Boolean>
+ 	^UseTypePool ifNil: [true]!

Item was added:
+ ----- Method: ExternalType class>>useTypePool: (in category 'preferences') -----
+ useTypePool: aBoolean
+ 
+ 	UseTypePool = aBoolean ifTrue: [^ self].
+ 
+ 	UseTypePool := aBoolean.
+ 	
+ 	Cursor wait showWhile: [
+ 		"Either fill or clean out the type pool."
+ 		ExternalTypePool reset.
+ 		ExternalStructure defineAllFields.
+ 		ExternalTypePool cleanUp].!

Item was added:
+ ----- Method: ExternalType>>storeStringForField (in category 'external structure') -----
+ storeStringForField
+ 	"Answers the code snippet to be used to make use of the receiver during field access in an external structure."
+ 
+ 	^ self class useTypePool
+ 		ifTrue: [ExternalTypePool assuredPoolVarNameFor: self]
+ 		ifFalse: [self storeString]!

Item was changed:
  (PackageInfo named: 'FFI-Kernel') postscript: 'Smalltalk removeFromStartUpList: ExternalAddress.
  Smalltalk removeFromStartUpList: ExternalObject.
  
  "Introduce FFIAtomicReadWriteSend. All types need to be reset and all fields need to be re-defined."
+ ExternalType resetAllTypes.'!
- ExternalType resetAllTypes.
- ExternalStructure defineAllFields.
- '!



More information about the Squeak-dev mailing list