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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 4 17:09:12 UTC 2020


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

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

Name: FFI-Kernel-mt.92
Author: mt
Time: 4 June 2020, 7:09:12.449722 pm
UUID: d0fd6e1d-8ad7-d14d-b592-f129e45e93cb
Ancestors: FFI-Kernel-mt.91

Offer a more obvious way to define type aliases.

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

Item was changed:
  ----- Method: ExternalStructure class>>compileFields:withAccessors: (in category 'field definition') -----
  compileFields: specArray withAccessors: aSymbol 
  	"Compile a type specification for the FFI machinery.
  	Return the newly compiled spec.
  	Eventually generate the field accessors according to following rules:
  	- aSymbol = #always always generate the accessors
  	- aSymbol = #never never generate the accessors
  	- aSymbol = #generated only generate the auto-generated accessors
  	- aSymbol = #absent only generate the absent accessors"
  	| newByteAlignment byteOffset typeSpec newCompiledSpec |
+ 	(self isTypeAlias: specArray) ifTrue:
- 	(specArray size > 0 and: [specArray first class ~~ Array]) ifTrue:
  		[^ self compileAlias: specArray withAccessors: aSymbol].
  	byteOffset := 0.
  	newByteAlignment := self minStructureAlignment.
  	typeSpec := WriteStream on: (WordArray new: 10).
  	typeSpec nextPut: FFIFlagStructure.
  	specArray do: [:spec |
  		| fieldName fieldTypeName isPointerField externalType typeSize fieldAlignment |
  		fieldName := spec first.
  		fieldTypeName := spec second.
  		isPointerField := fieldTypeName last = $*.
  		fieldTypeName := (fieldTypeName findTokens: '*') first withBlanksTrimmed.
  		externalType := (ExternalType typeNamed: fieldTypeName)
  			ifNil: [self errorTypeNotFound: spec second].
  		isPointerField ifTrue: [externalType := externalType asPointerType].
  		typeSize := externalType byteSize.
  		fieldAlignment := (externalType byteAlignment
  			max: self minFieldAlignment)
  			min: self maxFieldAlignment.
  		byteOffset := byteOffset alignedTo: fieldAlignment.
  		newByteAlignment := newByteAlignment max: fieldAlignment.
  		spec size > 2 ifTrue: ["extra size"
  			spec third < typeSize
  				ifTrue: [^ self error: 'Explicit type size is less than expected'].
  			typeSize := spec third.
  		].
  		(fieldName notNil and: [self shouldGenerate: fieldName policy: aSymbol]) ifTrue: [
  			self defineFieldAccessorsFor: fieldName startingAt: byteOffset + 1 type: externalType.
  		].
  		typeSpec nextPutAll: (externalType embeddedSpecWithSize: typeSize).
  		byteOffset := byteOffset + typeSize.
  		].
  	
  	newByteAlignment := newByteAlignment min: self maxStructureAlignment.
  	byteOffset := byteOffset alignedTo: newByteAlignment.
  	newCompiledSpec := typeSpec contents.
  	newCompiledSpec at: 1 put: (byteOffset bitOr: FFIFlagStructure).
  	byteAlignment := newByteAlignment.
  	^ newCompiledSpec!

Item was changed:
  ----- Method: ExternalStructure class>>isTypeAlias (in category 'testing') -----
  isTypeAlias
- 	"Answer whether this structure is an alias for another C type, enum, etc."
- 	"Example: #( nil 'long' )"
  	
+ 	^ self isTypeAlias: self fields!
- 	| fields |
- 	^ (fields := self fields) size = 2
- 		and: [fields first isNil]!

Item was added:
+ ----- Method: ExternalStructure class>>isTypeAlias: (in category 'testing') -----
+ isTypeAlias: specArray
+ 	"Answer whether this structure is an alias for another C type, enum, etc."
+ 	"Example: #( nil 'long' )"
+ 	
+ 	^ (specArray size > 0 and: [specArray first class ~~ Array])!

Item was added:
+ ExternalStructure subclass: #ExternalTypeAlias
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Kernel'!
+ 
+ !ExternalTypeAlias commentStamp: 'mt 6/4/2020 19:02' prior: 0!
+ You can subclass from here to make type aliasing more clear.!

Item was added:
+ ----- Method: ExternalTypeAlias class>>fields (in category 'field definition') -----
+ fields
+ 
+ 	^ { nil. self originalTypeName }!

Item was added:
+ ----- Method: ExternalTypeAlias class>>isTypeAlias (in category 'testing') -----
+ isTypeAlias
+ 
+ 	^ true!

Item was added:
+ ----- Method: ExternalTypeAlias class>>originalTypeName (in category 'field definition') -----
+ originalTypeName
+ 	"Anser the typeName this alias should be for, e.g., 'long', 'ulonglong*', ..."
+ 	
+ 	self subclassResponsibility.!

Item was changed:
  ----- Method: ExternalUnion class>>compileFields:withAccessors: (in category 'field definition') -----
  compileFields: specArray withAccessors: aSymbol 
  	"Compile a type specification for the FFI machinery.
  	Return the newly compiled spec.
  	Eventually generate the field accessors according to the policy defined in aSymbol."
  	| byteOffset maxByteSize typeSpec newCompiledSpec newByteAlignment |
+ 	(self isTypeAlias: specArray) ifTrue:
+ 		[^ self error: 'Use ExternalStructure or ExternalTypeAlias to define a type alias, not ExternalUnion'].
- 	(specArray size > 0 and: [specArray first class ~~ Array]) ifTrue:
- 		[^ self error: 'Use ExternalStructure to define a type alias, not ExternalUnion'].
  	byteOffset := 1.
  	newByteAlignment := 1.
  	maxByteSize := 0.
  	typeSpec := WriteStream on: (WordArray new: specArray size + 1).
  	typeSpec nextPut: FFIFlagStructure.
  	specArray do: [:spec |
  		| fieldName fieldTypeName isPointerField externalType typeSize typeAlignment |
  		fieldName := spec first.
  		fieldTypeName := spec second.
  		isPointerField := fieldTypeName last = $*.
  		fieldTypeName := (fieldTypeName findTokens: '*') first withBlanksTrimmed.
  		externalType := (ExternalType typeNamed: fieldTypeName)
  			ifNil: [self errorTypeNotFound: spec second].
  		isPointerField ifTrue: [externalType := externalType asPointerType].
  		typeSize := externalType byteSize.
  		typeAlignment := externalType byteAlignment.
  		spec size > 2 ifTrue: ["extra size"
  			spec third < typeSize
  				ifTrue: [^ self error: 'Explicit type size is less than expected'].
  			typeSize := spec third.
  		].
  		(fieldName notNil and: [self shouldGenerate: fieldName policy: aSymbol]) ifTrue: [
  			self defineFieldAccessorsFor: fieldName startingAt: byteOffset type: externalType.
  		].
  		typeSpec nextPutAll: (externalType embeddedSpecWithSize: typeSize).
  		maxByteSize := maxByteSize max: typeSize.
  		newByteAlignment := newByteAlignment max: typeAlignment
  		].
  	maxByteSize := maxByteSize alignedTo: newByteAlignment.
  	newCompiledSpec := typeSpec contents.
  	newCompiledSpec at: 1 put: (maxByteSize bitOr: FFIFlagStructure).
  	byteAlignment := newByteAlignment.
  	^ newCompiledSpec!



More information about the Squeak-dev mailing list