[squeak-dev] FFI Inbox: FFI-Kernel-nice.119.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Jun 21 20:34:02 UTC 2020


Nicolas Cellier uploaded a new version of FFI-Kernel to project FFI Inbox:
http://source.squeak.org/FFIinbox/FFI-Kernel-nice.119.mcz

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

Name: FFI-Kernel-nice.119
Author: nice
Time: 21 June 2020, 10:34:00.334284 pm
UUID: 3f2eca9d-8f55-476c-a0b0-c5ed6368a6b4
Ancestors: FFI-Kernel-nice.118

Make the compiledSpecs of struct pointers conform to the experimental FFI branch (thru #adjustPointerType)

See https://github.com/OpenSmalltalk/opensmalltalk-vm/tree/experimental_FFI

Simplify a bit ExternalData access (at: / at:put:).
The assumption that ExternalDataType is the type of the contents and not the type of the reference helps simplifying IMO.

We might want to make it more complete once we deal with pointer arity.
It's not the case yet.

=============== Diff against FFI-Kernel-nice.118 ===============

Item was changed:
  ----- Method: ExternalData>>at: (in category 'accessing') -----
  at: index
  
- 	self
- 		assert: [index = 1 or: [type isAtomic]]
- 		description: 'Should not read non-atomic pointer as array'.
- 
  	((1 > index) or: [size notNil and: [index > size]])
  		ifTrue: [^ self errorSubscriptBounds: index].
  
+ 	^ type
- 	^ type asNonPointerType
  		handle: handle
+ 		at: ((index-1) * type byteSize) + 1!
- 		at: ((index-1) * type asNonPointerType byteSize) + 1!

Item was changed:
  ----- Method: ExternalData>>at:put: (in category 'accessing') -----
  at: index put: value
  
- 	self
- 		assert: [index = 1 or: [type isAtomic]]
- 		description: 'Should not read non-atomic pointer as array'.
- 
  	((1 > index) or: [size notNil and: [index > size]])
  		ifTrue: [^ self errorSubscriptBounds: index].
  
+ 	^ type
- 	^ type asNonPointerType
  		handle: handle
+ 		at: ((index-1) * type byteSize) + 1
- 		at: ((index-1) * type asNonPointerType byteSize) + 1
  		put: value!

Item was changed:
  ----- Method: ExternalStructure class>>compileAllFields (in category 'system startup') -----
  compileAllFields
  	"
  	ExternalStructure compileAllFields
  	"
+ 	| priorAuthorInitials |
- 	| priorAuthorInitials fieldSpec |
  	priorAuthorInitials := Utilities authorInitialsPerSe.
  	[Utilities setAuthorInitials: 'FFI'.
  	
  		self allStructuresInCompilationOrder do: [:structClass |
+ 			| fieldSpec |
  			fieldSpec := structClass fields.
  			self flag: #discuss. "mt: Why do we need that extra layout check? Performance gain is minimal..."
  			(structClass hasFieldLayoutChanged: fieldSpec)
  				ifTrue: [structClass compileFieldsSilently: fieldSpec].
  			structClass externalType "asNonPointerType"
  				compiledSpec: structClass compiledSpec;
+ 				byteAlignment: structClass byteAlignment;
+ 				adjustPointerType.
- 				byteAlignment: structClass byteAlignment.
  			structClass organization removeEmptyCategories].
  		"Compilation of fields only needs external types temporarily. Non-weak references to external types are only in methods with FFI calls."
  		ExternalType cleanupUnusedTypes.
  
  	] ensure: [Utilities setAuthorInitials: priorAuthorInitials]!

Item was added:
+ ----- Method: ExternalStructureType>>adjustPointerType (in category 'private') -----
+ adjustPointerType
+ 	self isPointerType
+ 		ifFalse: [self asPointerType
+ 				compiledSpec: (WordArray with: ((self compiledSpec first
+ 						bitAnd: FFIFlagAtomic + FFIFlagStructure)
+ 						bitOr: self class pointerSpec));
+ 				 byteAlignment: self class pointerAlignment]!

Item was changed:
  ----- Method: ExternalType class>>initializeStructureTypes (in category 'class initialization') -----
  initializeStructureTypes
  	"Reset all non-pointer struct types to zero and their pointer companions to the appropriate pointer size."
  
  	StructTypes ifNil: [
  		StructTypes := WeakValueDictionary new].
  	
  	self cleanupUnusedTypes.
  	
  	StructTypes valuesDo:[:structType |
  		structType "asNonPointerType"
  			compiledSpec: (WordArray with: self structureSpec);
  			byteAlignment: nil.
  		structType asPointerType
+ 			compiledSpec: (WordArray with: self pointerSpec + self structureSpec);
- 			compiledSpec: (WordArray with: self pointerSpec);
  			byteAlignment: nil].!

Item was changed:
  ----- Method: ExternalType>>handle:at: (in category 'external data') -----
  handle: handle at: byteOffset
  	"Read the receiver's external type using the given handle and the byteOffset. This is the dynamic version of #readFieldAt:."
  	
+ 	| address value |
- 	| result |
- 	self checkType.
- 	
  	self isPointerType
+ 		ifTrue:
+ 			[address := handle pointerAt: byteOffset length: self byteSize.
+ 			^ExternalData
+ 				fromHandle: address
+ 				type: self asNonPointerType].
+ 	self isAtomic
+ 		ifTrue:
+ 			["Answer atomic value"
+ 			value := handle
- 		ifFalse: [
- 			"Answer atomic value"
- 			^ handle
  				perform: (AtomicSelectors at: self atomicType)
+ 				with: byteOffset.
+ 			^referentClass ifNil: [value] ifNotNil: [referentClass fromHandle: value]].
+ 
+ 	referentClass isNil
+ 		ifTrue: [self error: 'unknown type'].
+ 	self isEmpty ifTrue: [self error: 'Empty structure'].
+ 		
+ 	^referentClass fromHandle: (handle structAt: byteOffset length: self byteSize)!
- 				with: byteOffset]
- 		ifTrue: [
- 			^ referentClass
- 				ifNotNil: [
- 					"Answer structure, union, or type alias"
- 					referentClass fromHandle: (handle pointerAt: byteOffset length: self byteSize)]
- 				ifNil: [
- 					"Answer wrapper that points to external data"
- 					result := ExternalData
- 						fromHandle: (handle pointerAt: byteOffset length: self byteSize)
- 						type: self.
- 					self = ExternalType string
- 						ifTrue: [result fromCString]
- 						ifFalse: [result]]]!

Item was changed:
  ----- Method: ExternalType>>handle:at:put: (in category 'external data') -----
  handle: handle at: byteOffset put: value
  	"Write a value using the receiver's external type at the given handle and byteOffset. This is the dynamic version of #writeFieldAt:with:."
  
- 	self checkType.
- 	
  	self isPointerType
- 		ifFalse: [ "set atomic value"
- 			self flag: #addTypeCheck. "mt: Note that there is currently no mapping from objects that represent valid atomics to atomic types."
- 			handle
- 				perform: ((AtomicSelectors at: self atomicType), 'put:') asSymbol
- 				with: byteOffset
- 				with: value]
  		ifTrue: [ "set pointer to struct/union/alias"
+ 			self assert: [value externalType == self asNonPointerType].
- 			self assert: [value externalType == self].
  			handle
  				pointerAt: byteOffset
  				put: value getHandle
+ 				length: self byteSize.
+ 			^value].
+ 		
+ 	self isAtomic
+ 		ifTrue:
+ 			[ "set atomic value"
+ 			self flag: #addTypeCheck. "mt: Note that there is currently no mapping from objects that represent valid atomics to atomic types."
+ 			handle
+ 				perform: ((AtomicSelectors at: self atomicType), 'put:') asSymbol
+ 				with: byteOffset
+ 				with: value.
+ 			^value].
+ 			
+ 	referentClass isNil
+ 		ifTrue: [self error: 'unknown type'].
+ 	self isEmpty ifTrue: [self error: 'Empty structure'].
+ 
+ 	self assert: [value externalType == self].
+ 	handle structAt: byteOffset put: value getHandle length: self byteSize.
+ 	^value
+ 	!
- 				length: self byteSize].!



More information about the Squeak-dev mailing list