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

commits at source.squeak.org commits at source.squeak.org
Thu May 20 17:35:07 UTC 2021


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

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

Name: FFI-Kernel-mt.162
Author: mt
Time: 20 May 2021, 7:35:06.00258 pm
UUID: 438d5218-def5-7e48-8016-e53905db2a19
Ancestors: FFI-Kernel-mt.161

For genuine atomic types (i.e. no type alias), speeds up dynamic array access, i.e. ExternalData >> #at:(put:). For all types, also speed up pointer/non-pointer conversion and #isVoid check.

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

Item was added:
+ ----- Method: ExternalArrayType>>asNonPointerType (in category 'converting') -----
+ asNonPointerType
+ 
+ 	^ self!

Item was added:
+ ----- Method: ExternalArrayType>>asPointerType (in category 'converting') -----
+ asPointerType
+ 
+ 	^ referencedType!

Item was added:
+ ----- Method: ExternalArrayType>>isVoid (in category 'testing') -----
+ isVoid
+ 
+ 	^ false!

Item was added:
+ ----- Method: ExternalAtomicType>>asNonPointerType (in category 'converting') -----
+ asNonPointerType
+ 
+ 	^ self!

Item was added:
+ ----- Method: ExternalAtomicType>>asPointerType (in category 'converting') -----
+ asPointerType
+ 
+ 	^ referencedType!

Item was added:
+ ----- Method: ExternalAtomicType>>handle:atIndex: (in category 'external data') -----
+ handle: handle atIndex: index
+ 	"Overwritten to use cached byteSize in atomic sends for performance."
+ 	
+ 	referentClass == nil ifTrue: [
+ 		^ (AtomicSends at: self atomicType + 1) first
+ 				handle: handle
+ 				atIndex: index].
+ 	^ super handle: handle atIndex: index!

Item was added:
+ ----- Method: ExternalAtomicType>>handle:atIndex:put: (in category 'external data') -----
+ handle: handle atIndex: index put: value
+ 	"Overwritten to use cached byteSize in atomic sends for performance."
+ 	
+ 	referentClass == nil ifTrue: [
+ 		^ (AtomicSends at: self atomicType + 1) second
+ 				handle: handle
+ 				atIndex: index
+ 				put: value].
+ 	^ super handle: handle atIndex: index put: value!

Item was added:
+ ----- Method: ExternalAtomicType>>isVoid (in category 'testing') -----
+ isVoid
+ 
+ 	^ self atomicType = 0!

Item was changed:
  ExternalStructure subclass: #ExternalData
+ 	instanceVariableNames: 'type contentType'
+ 	classVariableNames: 'AllowDetectForUnknownSize ExtraSizeChecks'
- 	instanceVariableNames: 'type'
- 	classVariableNames: 'AllowDetectForUnknownSize'
  	poolDictionaries: ''
  	category: 'FFI-Kernel'!
  
  !ExternalData commentStamp: 'mt 6/13/2020 17:26' prior: 0!
  Instances of ExternalData explicitly describe objects with associated type. They can be used for describing atomic C types like arrays of atomic types (e.g., 'int[]') or pointer to atomic types (e.g., 'int *').
  
  Instance variables:
  	type	<ExternalType>	The external type of the receiver. Always a pointer type.
  
  The encoding of type is equivalent to that of the basic type in class ExternalType. The interpretation of whether the receiver describes an array of data or a pointer to data depends on the contents of the instance variable 'handle'. If handle contains an ExternalAddress the receiver is treated as pointer to type. If the handle contains a ByteArray the receiver is interpreted as describing an array of type. Note that both interpretations are treated equivalent in external calls, e.g., if one describes an argument to an external call as taking 'int*' then, depending on the type of handle either the actual contents (if ExternalAddress) or a pointer to the contents (if ByteArray) is passed.
  
  !

Item was added:
+ ----- Method: ExternalData class>>extraSizeChecks (in category 'preferences') -----
+ extraSizeChecks
+ 	<preference: 'Extra size checks'
+ 		categoryList: #('FFI Kernel')
+ 		description: 'When true, there will be extra out-of-bounds checks when accessing external data with a known array size.'
+ 		type: #Boolean>
+ 	^ ExtraSizeChecks ifNil: [false]!

Item was added:
+ ----- Method: ExternalData class>>extraSizeChecks: (in category 'preferences') -----
+ extraSizeChecks: aBoolean
+ 
+ 	ExtraSizeChecks := aBoolean.!

Item was changed:
  ----- Method: ExternalData>>arrayType (in category 'accessing - types') -----
  arrayType
  	"Answer this container's array type or 'nil' if unknown."
  	
  	| arrayType |
+ 	^ (arrayType := self containerType) isVoid
- 	type ifNil: [^ nil].
- 	arrayType := self containerType asNonPointerType.
- 	^ arrayType isVoid
- 		ifTrue: [nil]
  		ifFalse: [arrayType]!

Item was changed:
  ----- Method: ExternalData>>at: (in category 'accessing') -----
  at: index
  
+ 	ExtraSizeChecks == true ifTrue: [self sizeCheck: index].
- 	((1 > index) or: [self size notNil and: [index > self size]])
- 		ifTrue: [^ self errorSubscriptBounds: index].
  
  	^ self contentType
  		handle: handle
+ 		atIndex: index!
- 		at: ((index-1) * self contentType byteSize) + 1!

Item was changed:
  ----- Method: ExternalData>>at:put: (in category 'accessing') -----
  at: index put: value
  
+ 	ExtraSizeChecks == true ifTrue: [self sizeCheck: index].
+ 	
- 	((1 > index) or: [self size notNil and: [index > self size]])
- 		ifTrue: [^ self errorSubscriptBounds: index].
- 
  	^ self contentType
  		handle: handle
+ 		atIndex: index
- 		at: ((index-1) * self contentType byteSize) + 1
  		put: value!

Item was changed:
  ----- Method: ExternalData>>contentType (in category 'accessing - types') -----
  contentType "^ <ExternalType>"
  	"Answer the content type for the current container type."
  
+ 	^ contentType ifNil: [
+ 		contentType := self arrayType
+ 			ifNil: [ExternalType void]
+ 			ifNotNil: [:arrayType | arrayType contentType]]!
- 	^ self arrayType
- 		ifNil: [ExternalType void]
- 		ifNotNil: [:arrayType | arrayType contentType]!

Item was changed:
  ----- Method: ExternalData>>externalType (in category 'accessing - types') -----
  externalType "^ <ExternalType>"
  	"Overwritten to answer our #containerType, which is important so that clients can then send #byteSize to the result."
+ 
+ 	^ handle isExternalAddress
+ 		ifTrue: [self containerType asPointerType]
+ 		ifFalse: [self containerType asNonPointerType]!
- 	
- 	^ self containerType!

Item was changed:
  ----- Method: ExternalData>>from:to: (in category 'accessing') -----
  from: firstIndex to: lastIndex
  	"Only copy data if already in object memory, that is, as byte array. Only check size if configured."
  
  	| byteOffset numElements byteSize contentType |
+ 	ExtraSizeChecks == true ifTrue: [
+ 		self sizeCheck: firstIndex.
+ 		self sizeCheck: lastIndex].
- 	((1 > firstIndex) or: [self size notNil and: [lastIndex > self size]])
- 		ifTrue: [^ self errorSubscriptBounds: lastIndex].
  
  	contentType := self contentType.
  	byteOffset := ((firstIndex-1) * contentType byteSize)+1.
  	numElements := lastIndex - firstIndex + 1 max: 0.
  	byteSize := numElements * contentType byteSize.
  
  	^ ExternalData
  		fromHandle: (handle structAt: byteOffset length: byteSize)
  		type: contentType
  		size: numElements!

Item was changed:
  ----- Method: ExternalData>>setType: (in category 'private') -----
  setType: externalType
  	"Private. Set the type used to derive content and container types. If you want to change the content type later, use #setContentType:."
  
  	externalType = ExternalType string ifTrue: [
  		^ self setType: externalType asNonPointerType].
  
+ 	(externalType isArrayType or: [externalType isVoid])
- 	(externalType asNonPointerType isArrayType or: [externalType isVoid])
  		ifTrue: [type := externalType]
  		ifFalse: [type := (externalType asArrayType: nil)].
  		
+ 	contentType := nil.!
- 	handle isExternalAddress
- 		ifTrue: [type := type asPointerType]
- 		ifFalse: [type := type asNonPointerType].!

Item was added:
+ ----- Method: ExternalData>>sizeCheck: (in category 'private') -----
+ sizeCheck: index
+ 
+ 	| sz |
+ 	((1 > index) or: [(sz := self size) notNil and: [index > sz]])
+ 		ifTrue: [^ self errorSubscriptBounds: index].!

Item was changed:
  ----- Method: ExternalData>>typeCheck (in category 'private') -----
  typeCheck
  	"Check type. If you happen to have a regular pointer type here, convert it into array type of unknown size. This can happen for result values of FFI calls if the signature did not specify, e.g., 'int[]' but 'int*'."
  	
+ 	type asNonPointerType isVoid "void*"
- 	type asNonPointerType isVoid
  		ifTrue: [^ self].
  	
+ 	type isArrayType
- 	type asNonPointerType isArrayType
  		ifFalse: [self setType: type "int*" asNonPointerType "int ... to become int[], not int*[]"].!

Item was added:
+ ----- Method: ExternalPointerType>>asNonPointerType (in category 'converting') -----
+ asNonPointerType
+ 
+ 	^ referencedType!

Item was added:
+ ----- Method: ExternalPointerType>>asPointerType (in category 'converting') -----
+ asPointerType
+ 
+ 	^ self!

Item was added:
+ ----- Method: ExternalPointerType>>isVoid (in category 'testing') -----
+ isVoid
+ 
+ 	^ false!

Item was added:
+ ----- Method: ExternalStructureType>>asNonPointerType (in category 'converting') -----
+ asNonPointerType
+ 
+ 	^ self!

Item was added:
+ ----- Method: ExternalStructureType>>asPointerType (in category 'converting') -----
+ asPointerType
+ 
+ 	^ referencedType!

Item was added:
+ ----- Method: ExternalStructureType>>isVoid (in category 'testing') -----
+ isVoid
+ 
+ 	^ false!

Item was added:
+ ----- Method: ExternalType>>handle:atIndex: (in category 'external data') -----
+ handle: handle atIndex: index
+ 
+ 	^ self
+ 		handle: handle
+ 		at: ((index-1) * self byteSize) + 1!

Item was added:
+ ----- Method: ExternalType>>handle:atIndex:put: (in category 'external data') -----
+ handle: handle atIndex: index put: value
+ 
+ 	^ self
+ 		handle: handle
+ 		at: ((index-1) * self byteSize) + 1
+ 		put: value!

Item was changed:
  MessageSend subclass: #FFIAtomicReadWriteSend
+ 	instanceVariableNames: 'byteSize'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'FFI-Kernel-Support'!
  
  !FFIAtomicReadWriteSend commentStamp: 'mt 5/19/2021 10:20' prior: 0!
  I am a message send for reading and writing atomic values from and to byte arrays or external addresses.
  
  I can help with code generation through #template.
  
  Take a look at ExternalType class >> #initializeAtomicSends.!

Item was added:
+ ----- Method: FFIAtomicReadWriteSend>>byteSize (in category 'accessing') -----
+ byteSize
+ 
+ 	^ byteSize!

Item was added:
+ ----- Method: FFIAtomicReadWriteSend>>byteSize: (in category 'accessing') -----
+ byteSize: numBytes
+ 
+ 	byteSize := numBytes.!

Item was changed:
  ----- Method: FFIAtomicReadWriteSend>>handle:at:put: (in category 'evaluating') -----
+ handle: receiver at: byteOffset put: value
- handle: receiver at: byteOffset put: floatValue
  	
  	self subclassResponsibility.!

Item was added:
+ ----- Method: FFIAtomicReadWriteSend>>handle:atIndex: (in category 'evaluating') -----
+ handle: receiver atIndex: index
+ 
+ 	^ self
+ 		handle: receiver
+ 		at: ((index-1) * self byteSize) + 1!

Item was added:
+ ----- Method: FFIAtomicReadWriteSend>>handle:atIndex:put: (in category 'evaluating') -----
+ handle: receiver atIndex: index put: value
+ 
+ 	^ self
+ 		handle: receiver
+ 		at: ((index-1) * self byteSize) + 1
+ 		put: value!

Item was changed:
+ ----- Method: FFIAtomicReadWriteSend>>printOn: (in category 'printing') -----
- ----- Method: FFIAtomicReadWriteSend>>printOn: (in category 'nil') -----
  printOn: stream
  
  	stream nextPutAll: self template.!

Item was changed:
  ----- Method: FloatReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: type
  
  	| selectors |
  	selectors := self lookupSelectorsFor: type.
  	^ {
  	
+ 	(self
- 	self
  		receiver: nil "handle" selector: selectors first
  		arguments: (Array
+ 			with: nil "byteOffset"))
+ 		byteSize: type byteSize;
+ 		yourself.
- 			with: nil "byteOffset").
  			
+ 	(self
- 	self
  		receiver: nil "handle" selector: selectors second
  		arguments: (Array
  			with: nil "byteOffset"
+ 			with: nil "aFloat"))
+ 		byteSize: type byteSize;
+ 		yourself
- 			with: nil "aFloat")
  
  }!

Item was changed:
  ----- Method: IntegerReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: type
  	"Overwritten to account for byteSize and isSigned."
  	
  	| selectors |
  	selectors := self lookupSelectorsFor: type.
  	^ {
  	
+ 	(self
- 	self
  		receiver: nil "handle" selector: selectors first
  		arguments: (Array
  			with: nil "byteOffset"
  			with: type byteSize
+ 			with: type isSigned))
+ 		byteSize: type byteSize;
+ 		yourself.
- 			with: type isSigned).
  			
+ 	(self
- 	self
  		receiver: nil "handle" selector: selectors second
  		arguments: (Array
  			with: nil "byteOffset"
  			with: nil "integerValue"
  			with: type byteSize
+ 			with: type isSigned))
+ 		byteSize: type byteSize;
+ 		yourself.
- 			with: type isSigned)
- 
  }!



More information about the Squeak-dev mailing list