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

commits at source.squeak.org commits at source.squeak.org
Mon May 3 16:53:54 UTC 2021


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

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

Name: FFI-Kernel-mt.126
Author: mt
Time: 3 May 2021, 6:53:53.131479 pm
UUID: efa27be5-2153-1c47-b30f-b8d9ca10b1c8
Ancestors: FFI-Kernel-mt.125

Adds a transparent way to write into composite structures that reside in object memory: #writer. (Name is up for discussion, especially since the namespace for custom structs is limited.)

Adds #zeroMemory to remove information from internal or external memory. 

Fixes regression in ExternalData >> #free.

Adds sanity checks to ExternalStructure #new and #externalNew, which both made no sense for type aliases.

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

Item was added:
+ ----- Method: ByteArray>>zeroMemory (in category '*FFI-Kernel') -----
+ zeroMemory
+ 
+ 	self atAllPut: 0.!

Item was added:
+ ----- Method: ByteArray>>zeroMemory: (in category '*FFI-Kernel') -----
+ zeroMemory: numBytes
+ 
+ 	1  to: numBytes do: [:index |
+ 		self byteAt: index put: 0].!

Item was added:
+ ProtoObject subclass: #ByteArrayWriter
+ 	instanceVariableNames: 'byteOffset byteSize byteArray'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Kernel'!
+ 
+ !ByteArrayWriter commentStamp: 'mt 5/3/2021 17:44' prior: 0!
+ I am a transparent wrapper over byte-array handles to allow access and manipulation just like through an external address.!

Item was added:
+ ----- Method: ByteArrayWriter class>>on: (in category 'instance creation') -----
+ on: handle
+ 
+ 	self assert: [handle isInternalMemory].
+ 	^ self new setArray: handle!

Item was added:
+ ----- Method: ByteArrayWriter>>doesNotUnderstand: (in category 'system primitives') -----
+ doesNotUnderstand: aMessage
+ 
+ 	| selector args |
+ 	selector := aMessage selector.
+ 	args := aMessage arguments.
+ 	args size caseOf: {
+ 		[ 1 ] -> [ (selector endsWith: 'At:') ifTrue: [ args at: 1 put: args first  + byteOffset ] ].
+ 		[ 2 ] -> [ (selector endsWith: 'length:')
+ 			ifTrue: [
+ 				args at: 1 put: args first + byteOffset.
+ 				args first + args second > byteSize
+ 					ifTrue: [self errorSubscriptBounds: args first + args second] ]
+ 			ifFalse: [(selector endsWith: 'put:') ifTrue: [
+ 				args at: 1 put: args first + byteOffset	]] ].
+ 		[ 3 ] -> [ (selector endsWith: 'length:')
+ 			ifTrue: [
+ 				args at: 1 put: args first + byteOffset.
+ 				args first + args third > byteSize
+ 					ifTrue: [self errorSubscriptBounds: args first + args third]]] 
+ 		} otherwise: []. 				
+ 	^ aMessage sendTo: byteArray!

Item was added:
+ ----- Method: ByteArrayWriter>>errorSubscriptBounds: (in category 'initialization') -----
+ errorSubscriptBounds: index
+ 
+ 	Error signal: 'subscript is out of bounds: ' , index printString.!

Item was added:
+ ----- Method: ByteArrayWriter>>setArray: (in category 'initialization') -----
+ setArray: aByteArray
+ 
+ 	byteArray := aByteArray.
+ 	byteOffset := 0.
+ 	byteSize := aByteArray size.!

Item was added:
+ ----- Method: ByteArrayWriter>>setArray:offset:size: (in category 'initialization') -----
+ setArray: aByteArray offset: aByteOffset size: aByteSize
+ 
+ 	byteArray := aByteArray.
+ 	byteOffset := aByteOffset.
+ 	byteSize := aByteSize.
+ 	
+ 	(byteOffset + byteSize > byteArray size)
+ 		ifTrue: [self errorSubscriptBounds: byteOffset + byteSize].!

Item was added:
+ ----- Method: ByteArrayWriter>>structAt:length: (in category 'accessing') -----
+ structAt: newByteOffset length: newLength
+ 
+ 	^ ByteArrayWriter new
+ 		setArray: byteArray
+ 		offset: byteOffset + newByteOffset - 1
+ 		size: newLength!

Item was added:
+ ----- Method: ByteArrayWriter>>structAt:put:length: (in category 'accessing') -----
+ structAt: newByteOffset put: value length: newLength
+ 
+ 	(newByteOffset + newLength > byteSize)
+ 		ifTrue: [self errorSubscriptBounds: newByteOffset + newLength].
+ 
+ 	^ byteArray
+ 		structAt: byteOffset + newByteOffset - 1
+ 		put: value
+ 		length: newLength!

Item was added:
+ ----- Method: Character class>>zero (in category '*FFI-Kernel') -----
+ zero
+ 	"See ExternalStructure >> #zeroMemory."
+ 	
+ 	^ $0!

Item was added:
+ ----- Method: ExternalAddress>>zeroMemory (in category 'initialize-release') -----
+ zeroMemory
+ 	"We need length information in bytes."
+ 	self shouldNotImplement.!

Item was added:
+ ----- Method: ExternalData>>free (in category 'initialize-release') -----
+ free
+ 
+ 	super free.
+ 	size := nil.!

Item was added:
+ ----- Method: ExternalData>>zeroMemory (in category 'initialize-release') -----
+ zeroMemory
+ 	"Remove all information but keep the memory allocated."
+ 
+ 	self sizeCheck.
+ 
+ 	handle isExternalAddress
+ 		ifTrue: [handle zeroMemory: self size * self contentType byteSize]
+ 		ifFalse: [ "ByteArray" handle zeroMemory].!

Item was changed:
  ----- Method: ExternalStructure class>>externalNew (in category 'instance creation') -----
  externalNew
  	"Create an instance of the receiver on the external heap"
+ 
+ 	^ self fromHandle: (self externalType isTypeAliasForAtomic
+ 		ifTrue: [self error: 'This is an alias-for-atomic type. You must use #fromHandle:']
+ 		ifFalse: [
+ 			self externalType isTypeAliasForPointer
+ 				ifTrue: [ByteArray new: self byteSize]
+ 				ifFalse: [ExternalAddress allocate: self byteSize]])!
- 	^self fromHandle: (ExternalAddress allocate: self byteSize)!

Item was changed:
  ----- Method: ExternalStructure class>>new (in category 'instance creation') -----
  new
+ 	^self fromHandle: (self externalType isTypeAliasForAtomic
+ 		ifTrue: [self error: 'This is an alias-for-atomic type. You must use #fromHandle:']
+ 		ifFalse: [ByteArray new: self byteSize]).!
- 	^self fromHandle: (ByteArray new: self byteSize)!

Item was added:
+ ----- Method: ExternalStructure class>>newZero (in category 'instance creation') -----
+ newZero
+ 
+ 	^ self new
+ 		zeroMemory;
+ 		yourself!

Item was added:
+ ----- Method: ExternalStructure>>writer (in category 'accessing') -----
+ writer
+ 
+ 	^ handle isInternalMemory
+ 		"Wrap handle into helper to address offsets in the byte array."
+ 		ifTrue: [self class fromHandle: (ByteArrayWriter on: handle)]
+ 		"Either alias-to-atomic or already in external memory."
+ 		ifFalse: [self]!

Item was added:
+ ----- Method: ExternalStructure>>zeroMemory (in category 'initialize-release') -----
+ zeroMemory
+ 	"Remove all information but keep the memory allocated."
+ 
+ 	handle isExternalAddress
+ 		ifTrue: [handle zeroMemory: self externalType byteSize]
+ 		ifFalse: [handle isInternalMemory
+ 			ifTrue: [handle zeroMemory]
+ 			ifFalse: [
+ 				"Alias-to-atomic type."
+ 				handle := handle class zero]].!



More information about the Squeak-dev mailing list