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

commits at source.squeak.org commits at source.squeak.org
Fri Aug 6 16:13:18 UTC 2021


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

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

Name: FFI-Kernel-mt.187
Author: mt
Time: 6 August 2021, 6:13:15.076096 pm
UUID: 7f872bc6-73da-eb43-b853-b8f21aea19a3
Ancestors: FFI-Kernel-eem.186

Clean up recent changes around new integer primitives in ByteArray:
- Revert some error handling which was only necessary due to a wrong postscript; see details below
- Re-add the #floatAt:(put:) backstop in Float32Array for #handle:at:(put:) interface; see all senders of #atByteOffset:(put:)
- Refactor FFIAtomicReadWriteSend hierarchy to better reflect direct and indirect (or generic) mappings between atomic types and their primitive sends
- Fix regression in ByteArray >> #zeroMemory:
- Fix bug around ExternalAddress and #zeroMemory
- Speed up #contentType for raw-bits arrays

Note that changes to atomic types require a #resetAllAtomicTypes, not #initializeAtomicTypes. This will also update images that already use older FFI versions. ExternalType class >> #initialize is currently *not* able to migrate to newer FFI versions.

Note that it makes no sense to mark more than one primitive responsible for #ffiAtomicRead: or #ffiAtomicWrite:. Thus, it is not necessary to prioritize matches in #lookupSelectorsFor:. Just take the first lookup result. Primitive-fallback code is used to delegate to the generic integer primitives.

Note that #methodsDo: in ByteArray -- having about 100 methods -- with checking for pragmas in each method is way faster (!!) than filtering by class organization and message category first. About 4 times. There is no fast way to reduce the search/lookup space at the moment.

=============== Diff against FFI-Kernel-eem.186 ===============

Item was changed:
+ FFIAtomicReadWriteSend subclass: #BooleanReadWriteSend
- IntegerReadWriteSend subclass: #BooleanReadWriteSend
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'FFI-Kernel-Support'!
  
+ !BooleanReadWriteSend commentStamp: 'mt 8/6/2021 16:15' prior: 0!
- !BooleanReadWriteSend commentStamp: 'mt 5/19/2021 10:17' prior: 0!
  I am a specialization for the atomic 'bool' type, which maps to 'byte' but adds extra pre- and post-processing to read and write instances of Boolean, i.e. true and false.!

Item was changed:
  ----- Method: BooleanReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: type
  
  	^ super fromType: ExternalType byte!

Item was changed:
  ----- Method: BooleanReadWriteSend>>handle:at: (in category 'evaluating') -----
  handle: handle at: byteOffset
  
  	^ (super handle: handle at: byteOffset) ~= 0!

Item was changed:
  ----- Method: BooleanReadWriteSend>>handle:at:put: (in category 'evaluating') -----
  handle: handle at: byteOffset put: aBoolean
  
  	super
  		handle: handle
  		at: byteOffset
  		put: (aBoolean ifTrue: [1] ifFalse: [0]).
  	^ aBoolean!

Item was changed:
  ----- Method: BooleanReadWriteSend>>template (in category 'compiling') -----
  template
  
  	^ self isReading
  		ifTrue: ['(', super template, ') ~= 0']
  		ifFalse: [super template copyReplaceAll: '{3}' with: '({3} ifTrue: [1] ifFalse: [0])']!

Item was removed:
- ----- Method: ByteArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType uint8_t asArrayType: nil!

Item was added:
+ ----- Method: ByteArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType uint8_t!

Item was changed:
+ ----- Method: ByteArray>>doubleAt: (in category '*FFI-Kernel-accessing - float') -----
- ----- Method: ByteArray>>doubleAt: (in category '*FFI-Kernel-accessing') -----
  doubleAt: byteOffset	
  	"Primitive. Return a float value from the receiver.
  	- FAILS IF the receiver has not enough bytes for an IEEE 754 (64 bits) floating point number.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress.
  	- SEE Float class >> #fromIEEE64Bit: and Float >> #asIEEE64BitWord"
  	<primitive: #primitiveFFIDoubleAt module: #SqueakFFIPrims>
  	<ffiAtomicRead: #double>
  	"Examples:
  		ExternalType double handle: #[ 0 0 0 255 0 0 0 0 ] at: 1.
  		ExternalType double handle: #[ 0 0 0 255 ] at: 1. --- Error.
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>doubleAt:put: (in category '*FFI-Kernel-accessing - float') -----
- ----- Method: ByteArray>>doubleAt:put: (in category '*FFI-Kernel-accessing') -----
  doubleAt: byteOffset put: value
  	"Primitive. Store the given value as IEEE 754 (64 bits) floating point number.
  	- FAILS IF the receiver has not enough bytes for that representation.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress.
  	- SEE Float class >> #fromIEEE64Bit: and Float >> #asIEEE64BitWord"
  	<primitive: #primitiveFFIDoubleAtPut module: #SqueakFFIPrims>
  	<ffiAtomicWrite: #double>
  	"Examples:
  		ExternalType double allocate value: 123.4567890; explore
  		ExternalType double allocate value: 0.0001; explore
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>floatAt: (in category '*FFI-Kernel-accessing - float') -----
- ----- Method: ByteArray>>floatAt: (in category '*FFI-Kernel-accessing') -----
  floatAt: byteOffset
  	"Primitive. Return a float value from the receiver.
  	- FAILS IF the receiver has not enough bytes for an IEEE 754 (32 bits) floating point number.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress.
  	- SEE Float class >> #fromIEEE32Bit: and Float >> #asIEEE32BitWord"
  	<primitive: #primitiveFFIFloatAt module: #SqueakFFIPrims>
  	<ffiAtomicRead: #float>
  	"Examples:
  		ExternalType float handle: #[ 0 0 0 255 ] at: 1.
  		ExternalType float handle: #[ 0 0 255 ] at: 1. --- Error.
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>floatAt:put: (in category '*FFI-Kernel-accessing - float') -----
- ----- Method: ByteArray>>floatAt:put: (in category '*FFI-Kernel-accessing') -----
  floatAt: byteOffset put: value
  	"Primitive. Store the given value as IEEE 754 (32 bits) floating point number.
  	- FAILS IF the receiver has not enough bytes for that representation.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress.
  	- SEE Float class >> #fromIEEE32Bit: and Float >> #asIEEE32BitWord"
  	<primitive: #primitiveFFIFloatAtPut module: #SqueakFFIPrims>
  	<ffiAtomicWrite: #float>
  	"Examples:
  		ExternalType float allocate value: 123.4567890; explore
  		ExternalType float allocate value: 0.0001; explore
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>int16At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int16At: (in category '*FFI-Kernel-accessing') -----
  int16At: byteOffset
  	"Answer the signed 16-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt16At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #int16_t>
  	^ self integerAt: byteOffset size: 2 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int16At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int16At:put: (in category '*FFI-Kernel-accessing') -----
  int16At: byteOffset put: value
  	"Store the signed 16-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt16AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #int16_t>
  	^ self integerAt: byteOffset put: value size: 2 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int32At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int32At: (in category '*FFI-Kernel-accessing') -----
  int32At: byteOffset
  	"Answer the signed 32-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt32At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #int32_t>
  	^ self integerAt: byteOffset size: 4 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int32At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int32At:put: (in category '*FFI-Kernel-accessing') -----
  int32At: byteOffset put: value
  	"Store the signed 32-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt32AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #int32_t>
  	^ self integerAt: byteOffset put: value size: 4 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int64At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int64At: (in category '*FFI-Kernel-accessing') -----
  int64At: byteOffset
  	"Answer the signed 64-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt64At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #int64_t>
  	^ self integerAt: byteOffset size: 8 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int64At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int64At:put: (in category '*FFI-Kernel-accessing') -----
  int64At: byteOffset put: value
  	"Store the signed 64-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt64AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #int64_t>
  	^ self integerAt: byteOffset put: value size: 8 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int8At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int8At: (in category '*FFI-Kernel-accessing') -----
  int8At: byteOffset
  	"Answer the signed 8-bit integer at byte offset."
  	<primitive: #primitiveSignedInt8At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #int8_t>
  	^ self integerAt: byteOffset size: 1 signed: true!

Item was changed:
+ ----- Method: ByteArray>>int8At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>int8At:put: (in category '*FFI-Kernel-accessing') -----
  int8At: byteOffset put: value
  	"Store the signed 8-bit integer at byte offset."
  	<primitive: #primitiveSignedInt8AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #int8_t>
  	^ self integerAt: byteOffset put: value size: 1 signed: true!

Item was changed:
+ ----- Method: ByteArray>>integerAt:put:size:signed: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>integerAt:put:size:signed: (in category '*FFI-Kernel-accessing') -----
  integerAt: byteOffset put: value size: nBytes signed: aBoolean
  	"Primitive. Store the given value as integer of nBytes size in the receiver.
  	- BYTE ORDER is platform native order.
  	- FAILS IF the value is out of range.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress."
  	<primitive: #primitiveFFIIntegerAtPut module: #SqueakFFIPrims>
+ 	"<ffiAtomicWrite: #( int8_t uint8_t int16_t uint16_t int32_t uint32_t int64_t uint64_t ) >"
- 	<ffiAtomicWrite: #( int8_t uint8_t int16_t uint16_t int32_t uint32_t int64_t uint64_t ) >
  	"Examples:
  		ExternalType int32_t allocate value: -1; explore.
  		ExternalType uint32_t allocate value: 1; explore.
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>integerAt:size:signed: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>integerAt:size:signed: (in category '*FFI-Kernel-accessing') -----
  integerAt: byteOffset size: nBytes signed: aBoolean
  	"Primitive. Return an integer of nBytes size from the receiver.
  	- BYTE ORDER is platform native order.
  	- FAILS IF the receiver has not enough bytes.
  	- NOTE that this primitive will access memory in the outer space if invoked from ExternalAddress."
  	<primitive: #primitiveFFIIntegerAt module: #SqueakFFIPrims>
+ 	"<ffiAtomicRead: #( int8_t uint8_t int16_t uint16_t int32_t uint32_t int64_t uint64_t ) >"
- 	<ffiAtomicRead: #( int8_t uint8_t int16_t uint16_t int32_t uint32_t int64_t uint64_t ) >
  	"Examples:
  		ExternalType int32_t handle: #[ 255 0 0 255 ] at: 1.
  		ExternalType uint32_t handle: #[ 255 0 0 255 ] at: 1.	
  	"
  	^ self primitiveFailed!

Item was changed:
+ ----- Method: ByteArray>>uint16At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint16At: (in category '*FFI-Kernel-accessing') -----
  uint16At: byteOffset
  	"Answer the signed 16-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt16At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #uint16_t>
  	^ self integerAt: byteOffset size: 2 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint16At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint16At:put: (in category '*FFI-Kernel-accessing') -----
  uint16At: byteOffset put: value
  	"Store the unsigned 16-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveUnsignedInt16AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #uint16_t>
  	^ self integerAt: byteOffset put: value size: 2 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint32At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint32At: (in category '*FFI-Kernel-accessing') -----
  uint32At: byteOffset
  	"Answer the signed 32-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt32At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #uint32_t>
  	^ self integerAt: byteOffset size: 4 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint32At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint32At:put: (in category '*FFI-Kernel-accessing') -----
  uint32At: byteOffset put: value
  	"Store the unsigned 32-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveUnsignedInt32AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #uint32_t>
  	^ self integerAt: byteOffset put: value size: 4 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint64At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint64At: (in category '*FFI-Kernel-accessing') -----
  uint64At: byteOffset
  	"Answer the signed 64-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveSignedInt64At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #uint64_t>
  	^ self integerAt: byteOffset size: 8 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint64At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint64At:put: (in category '*FFI-Kernel-accessing') -----
  uint64At: byteOffset put: value
  	"Store the unsigned 64-bit integer at byte offset, in platform native order."
  	<primitive: #primitiveUnsignedInt64AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #uint64_t>
  	^ self integerAt: byteOffset put: value size: 8 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint8At: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint8At: (in category '*FFI-Kernel-accessing') -----
  uint8At: byteOffset
+ 	"Answer the unsigned 8-bit integer at byte offset. Same as #byteAt: and #at:."
- 	"Answer the unsigned 8-bit integer at byte offset."
  	<primitive: #primitiveUnsignedInt8At module: #SqueakFFIPrims error: ec>
  	<ffiAtomicRead: #uint8_t>
  	^ self integerAt: byteOffset size: 1 signed: false!

Item was changed:
+ ----- Method: ByteArray>>uint8At:put: (in category '*FFI-Kernel-accessing - integer') -----
- ----- Method: ByteArray>>uint8At:put: (in category '*FFI-Kernel-accessing') -----
  uint8At: byteOffset put: value
+ 	"Store the unsigned 8-bit integer at byte offset. Same as #byteAt:put: and #at:put:."
- 	"Store the unsigned 8-bit integer at byte offset."
  	<primitive: #primitiveUnsignedInt8AtPut module: #SqueakFFIPrims error: ec>
  	<ffiAtomicWrite: #uint8_t>
  	^ self integerAt: byteOffset put: value size: 1 signed: false!

Item was changed:
  ----- Method: ByteArray>>unsignedByteAt: (in category '*FFI-Kernel-accessing') -----
  unsignedByteAt: byteOffset
  	"Same as #byteAt: but different primitive to support ExternalAddress."
+ 
  	<primitive: #primitiveUnsignedInt8At module: #SqueakFFIPrims error: ec>
  	^ self integerAt: byteOffset size: 1 signed: false!

Item was changed:
  ----- Method: ByteArray>>unsignedByteAt:put: (in category '*FFI-Kernel-accessing') -----
  unsignedByteAt: byteOffset put: value
  	"Same as #byteAt: but different primitive to support ExternalAddress."
+ 
+ 	<primitive: #primitiveUnsignedInt8AtPut module: #SqueakFFIPrims error: ec>
- 		
  	^ self integerAt: byteOffset put: value size: 1 signed: false!

Item was changed:
  ----- Method: ByteArray>>zeroMemory: (in category '*FFI-Kernel-accessing') -----
  zeroMemory: numBytes
+ 	"Zero numBytes in the receiver. Try to set multiple bytes at once if possible. Simple algorithm looks as follows:
+ 	
+ 		1  to: numBytes do: [:index |
+ 			self unsignedByteAt: index put: 0].
+ 	"
  
  	| index size |
  	index := 1.
+ 	size := numBytes - 7.
- 	size := self size - 7.
  	[index <= size] whileTrue:
  		[self uint64At: index put: 0.
  		 index := index + 8].
+ 	size := size + 4. "7 - 3, i.e. numBytes - 3"
- 	size := size + 4. "7 - 3, i.e. self size - 3"
  	index <= size ifTrue:
  		[self uint32At: index put: 0.
  		 index := index + 4].
+ 	size := size + 2. "3 - 1, i.e. numBytes - 1"
- 	size := size + 2. "3 - 1, i.e. self size - 1"
  	index <= size ifTrue:
  		[self uint16At: index put: 0.
  		 index := index + 2].
+ 	size := size + 1.
+ 	index <= size ifTrue:
- 	index < size ifTrue:
  		[self uint8At: index put: 0]!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int16At: (in category 'read/write atomics') -----
+ int16At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int16At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int16At:put: (in category 'read/write atomics') -----
+ int16At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int16At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int32At: (in category 'read/write atomics') -----
+ int32At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int32At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int32At:put: (in category 'read/write atomics') -----
+ int32At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int32At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int64At: (in category 'read/write atomics') -----
+ int64At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int64At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int64At:put: (in category 'read/write atomics') -----
+ int64At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int64At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int8At: (in category 'read/write atomics') -----
+ int8At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int8At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int8At:put: (in category 'read/write atomics') -----
+ int8At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int8At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>perform:with: (in category 'message handling') -----
+ perform: aSymbol with: firstObject
+ 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:."
+ 	
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject }!

Item was added:
+ ----- Method: ByteArrayReadWriter>>perform:with:with: (in category 'message handling') -----
+ perform: aSymbol with: firstObject with: secondObject
+ 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:put:."
+ 	
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject. secondObject }!

Item was changed:
  ----- Method: ByteArrayReadWriter>>perform:with:with:with: (in category 'message handling') -----
  perform: aSymbol with: firstObject with: secondObject with: thirdObject 
+ 	"Needed because of AtomicSelectors. See GenericIntegerReadWriteSend >> #handle:at:."
- 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:."
  	
  	<primitive: 83>
  	^ self perform: aSymbol withArguments: { firstObject. secondObject. thirdObject }!

Item was changed:
  ----- Method: ByteArrayReadWriter>>perform:with:with:with:with: (in category 'message handling') -----
  perform: aSymbol with: firstObject with: secondObject with: thirdObject with: fourthObject
+ 	"Needed because of AtomicSelectors. See GenericIntegerReadWriteSend >> #handle:at:put:."
- 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:put:."
  
  	<primitive: 83>
  	^ self perform: aSymbol withArguments: { firstObject. secondObject. thirdObject. fourthObject }!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint16At: (in category 'read/write atomics') -----
+ uint16At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint16At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint16At:put: (in category 'read/write atomics') -----
+ uint16At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint16At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint32At: (in category 'read/write atomics') -----
+ uint32At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint32At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint32At:put: (in category 'read/write atomics') -----
+ uint32At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint32At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint64At: (in category 'read/write atomics') -----
+ uint64At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint64At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint64At:put: (in category 'read/write atomics') -----
+ uint64At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint64At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint8At: (in category 'read/write atomics') -----
+ uint8At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint8At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint8At:put: (in category 'read/write atomics') -----
+ uint8At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint8At: oByteOffset + byteOffset put: value!

Item was changed:
  ----- Method: ByteString class>>externalType (in category '*FFI-Kernel') -----
  externalType
  
+ 	^ self new contentType asArrayType: nil!
- 	^ ExternalType char asArrayType: nil!

Item was changed:
  ----- Method: ByteString>>contentType (in category '*FFI-Kernel-external data') -----
  contentType
  
+ 	^ ExternalType char!
- 	^ self externalType contentType!

Item was changed:
  ----- Method: ByteString>>externalType (in category '*FFI-Kernel-external data') -----
  externalType
  
+ 	^ self contentType asArrayType: self size!
- 	^ self class externalType contentType asArrayType: self size!

Item was added:
+ ----- Method: ByteString>>uint8At: (in category '*FFI-Kernel-accessing') -----
+ uint8At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: ByteString>>uint8At:put: (in category '*FFI-Kernel-accessing') -----
+ uint8At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value asCharacter!

Item was changed:
+ FFIAtomicReadWriteSend subclass: #CharacterReadWriteSend
- IntegerReadWriteSend subclass: #CharacterReadWriteSend
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'FFI-Kernel-Support'!
  
+ !CharacterReadWriteSend commentStamp: 'mt 8/6/2021 16:15' prior: 0!
- !CharacterReadWriteSend commentStamp: 'mt 5/19/2021 10:18' prior: 0!
  I am a specialization for the atomic 'char' and 'schar' types, which both map to (unsigned) 'byte' but add extra pre- and post-processing to read and write instances of Character such as $A and $Z.!

Item was changed:
  ----- Method: CharacterReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: type
  
  	^ super fromType: ExternalType byte!

Item was changed:
  ----- Method: CharacterReadWriteSend>>handle:at: (in category 'evaluating') -----
  handle: handle at: byteOffset
  
  	^ (super handle: handle at: byteOffset) asCharacter!

Item was changed:
  ----- Method: CharacterReadWriteSend>>handle:at:put: (in category 'evaluating') -----
  handle: handle at: byteOffset put: aCharacter
  
  	super
  		handle: handle
  		at: byteOffset
  		put: aCharacter asciiValue.
  	^ aCharacter!

Item was changed:
  ----- Method: CharacterReadWriteSend>>template (in category 'compiling') -----
  template
  
  	^ self isReading
  		ifTrue: ['(', super template, ') asCharacter']
  		ifFalse: [super template copyReplaceAll: '{3}' with: '{3} asciiValue']!

Item was removed:
- ----- Method: DoubleByteArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType uint16_t asArrayType: nil!

Item was added:
+ ----- Method: DoubleByteArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType uint16_t!

Item was added:
+ ----- Method: DoubleByteArray>>uint16At: (in category '*FFI-Kernel-accessing') -----
+ uint16At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: DoubleByteArray>>uint16At:put: (in category '*FFI-Kernel-accessing') -----
+ uint16At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: DoubleWordArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType uint64_t asArrayType: nil!

Item was added:
+ ----- Method: DoubleWordArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType uint64_t!

Item was added:
+ ----- Method: DoubleWordArray>>uint64At: (in category '*FFI-Kernel-accessing') -----
+ uint64At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: DoubleWordArray>>uint64At:put: (in category '*FFI-Kernel-accessing') -----
+ uint64At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: ExternalAddress>>zeroMemory (in category 'external data') -----
+ zeroMemory
+ 	"Overwritten for robustness. See RawBitsArray >> #zeroMemory."
+ 	
+ 	self shouldNotImplement. "Use #zeroMemory: instead."!

Item was changed:
  ----- Method: ExternalType class>>cleanupUnusedTypes (in category 'housekeeping') -----
  cleanupUnusedTypes
  	"In the lookup table for struct types and array types, remove keys to types no longer present..
  		
  	ExternalType cleanupUnusedTypes
  	"
  	Smalltalk garbageCollect.	
  	StructTypes keys do: [:key |
  		(StructTypes at: key) ifNil: [
  			StructTypes removeKey: key]].
  	
  	ArrayTypes keys do: [:contentTypeName |
  		| sizes |
  		sizes := ArrayTypes at: contentTypeName.
+ 		sizes keys do: [:size |
- 		[sizes keys do: [:size |
  			(sizes at: size) ifNil: [sizes removeKey: size]].
+ 		sizes ifEmpty: [
+ 			ArrayTypes removeKey: contentTypeName]].!
- 		 sizes ifEmpty: [
- 			ArrayTypes removeKey: contentTypeName]]
- 			on: Error
- 			do: [:ex| Transcript print: ex; cr; flush]]!

Item was changed:
  ----- Method: ExternalType class>>initializeArrayClasses (in category 'class initialization') -----
  initializeArrayClasses
  	"
  	ExternalType initializeArrayClasses.
  	"
  	ArrayClasses ifNil: [
  		ArrayClasses := IdentityDictionary new].
  	
  	RawBitsArray allSubclasses collect: [:arrayClass |
+ 		[ArrayClasses at: arrayClass new contentType ifAbsentPut: arrayClass]
+ 			on: Error do: [ "Ignore." ]].
- 		[ArrayClasses at: arrayClass externalType contentType ifAbsentPut: arrayClass]
- 			on: SubclassResponsibility do: [ "Ignore." ]].
  
  	ArrayClasses at: ExternalType unsignedChar put: ByteString.
  	ArrayClasses at: ExternalType signedChar put: ByteString.	!

Item was changed:
  ----- Method: ExternalType class>>initializeAtomicTypes (in category 'class initialization') -----
  initializeAtomicTypes
+ 	"Initializes atomic types if not already initialized. NOTE that if you want to reset already initialized atomic types, use #resetAllAtomicTypes instead."
- 	"ExternalType initialize"
  	
  	| atomicType byteSize type typeName byteAlignment |
  	self flag: #ffiLongVsInt. "For a discussion about long vs. int see http://forum.world.st/Re-squeak-dev-64-bit-FFI-was-porting-Croquet-to-Squeak6-0-alpha-tp5113318.html."
+ 	
- 	AtomicTypes do:
- 		[:anAtomicType|
- 		(anAtomicType class ~~ ExternalAtomicType
- 		 and: [anAtomicType class == ExternalType]) ifTrue:
- 			[ExternalAtomicType adoptInstance: anAtomicType]].
  	#(
  		"name		atomic id		byte size	byte alignment"
  		('void' 		0 				0			0) "No non-pointer support in calls. Duh. ;-)"
  		('bool' 		1 				1			1) "No pointer support in calls."
  		('byte' 		2 				1			1)
  		('sbyte' 	3 				1			1)
  		('ushort' 	4 				2			2)
  		('short' 		5 				2			2)
  "!!!!!!"	('ulong' 	6 				4 "!!!!!!"		4)
  "!!!!!!"	('long' 		7 				4 "!!!!!!"		4)
  		('ulonglong' 8 				8			8) "v.i."
  		('longlong' 	9 				8			8) "v.i."
  		('char' 		10 				1			1)
  		('schar' 	11 				1			1)
  		('float' 		12 				4			4)
  		('double' 	13 				8			8) "v.i."
  "TODO: ('longdouble' 14			10			16? 4?)"
  	) do:[:typeSpec| | compiled |
  		typeName := typeSpec first.
  		atomicType := typeSpec second.
  		byteSize := typeSpec third.
  		byteAlignment := typeSpec fourth.
  		
  		"0) On 32-bits Windows and MacOS, double and long long have an alignment of 8. But on 32-bit Linux, their alignment is 4. But not on a 32-bit Raspberry Pi OS."
  		(FFIPlatformDescription current wordSize = 4
  			and: [FFIPlatformDescription current isUnix
  			and: [FFIPlatformDescription current isARM not]]) ifTrue: [
  				(#('double' 'longlong' 'ulonglong') includes: typeName) ifTrue: [
  					byteAlignment := 4]].
  		
  		"1) Regular type"
  		type := (AtomicTypes at: typeName).
  		compiled := WordArray with: ((byteSize bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: byteAlignment.
  		
  		"2) Pointer type"
  		type := type asPointerType.
  		compiled := WordArray with: ((self pointerSpec bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: self pointerAlignment.
  	].!

Item was changed:
  ----- Method: ExternalType class>>initializeDefaultTypes (in category 'class initialization') -----
  initializeDefaultTypes
+ 	"Initializes atomic types and structure types. NOTE THAT if you want to reset already initialized types, use #resetAllTypes isntead."
- 	"Create new atomic types and setup the dictionaries. See #resetAllAtomicTypes."
  
  	AtomicTypes ifNil: [
  		AtomicTypes := Dictionary new. "Strong references required because there is no lazy atomic type initialization like there is for struct types and array types."
  		AtomicTypeNames valuesDo: [:typeName |
  			self newTypeForAtomicNamed: typeName]].
  	
  	self initializeAtomicTypes.
  	self initializeAtomicSends.
  	self initializeStructureTypes.!

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. NOTE THAT if you want to reset already initialized structure types, use #resetAllStructureTypes instead."
- 	"Reset all non-pointer struct types to zero and their pointer companions to the appropriate pointer size."
  
  	StructTypes ifNil: [
  		StructTypes := WeakValueDictionary new].
  	ArrayTypes ifNil: [
  		ArrayTypes := Dictionary new].
  	
  	self cleanupUnusedTypes.
  	
  	StructTypes valuesDo:[:structType |
  		structType "asNonPointerType"
  			compiledSpec: (WordArray with: self structureSpec);
  			byteAlignment: nil.
  		structType asPointerType
  			compiledSpec: (WordArray with: self pointerSpec);
  			byteAlignment: nil].
  	ArrayTypes valuesDo: [:sizes | sizes do: [:arrayType |
  		arrayType
  			compiledSpec: (WordArray with: (arrayType headerWord bitClear: FFIStructSizeMask));
  			byteAlignment: nil.
  		arrayType asPointerType
  			compiledSpec: (WordArray with: self pointerSpec);
  			byteAlignment: nil]].!

Item was changed:
  ----- Method: ExternalType class>>typeNamed: (in category 'instance lookup') -----
  typeNamed: typeName
  	"Supports pointer-type lookup for both atomic and structure types.
  	Examples: 'long', 'long*', 'long *' or 'MyStruct', 'MyStruct*', 'MyStruct *', 'IntPtr', '*IntPtr' "
  	
  	| isPointerType isNonPointerType isArrayType actualTypeName type |
+ 	isArrayType := false. isNonPointerType := false.
  	actualTypeName := typeName copyWithoutAll: ' '.
  
  	(isPointerType := actualTypeName last == $*) "e.g. MyStruct*"
  		ifTrue: [actualTypeName := actualTypeName allButLast].
  	actualTypeName last == $) "e.g. (char[])* -- pointer type for array type"
  		ifTrue: [actualTypeName := (actualTypeName copyFrom: 2 to: actualTypeName size - 1)].
  	(isNonPointerType := actualTypeName first == $*) "e.g. *DoublePtr"
  		ifTrue: [actualTypeName := actualTypeName allButFirst].
  
  	(isArrayType := actualTypeName last == $])
  		ifTrue: [ type := self arrayTypeNamed: actualTypeName ]
  		ifFalse: [
  			(Symbol lookup: actualTypeName)
  				ifNotNil: [:sym | actualTypeName := sym].
  			type := (self atomicTypeNamed: actualTypeName)
  				ifNil: [self structTypeNamed: actualTypeName]].
  
+ 	^ type ifNotNil: [
+ 		isPointerType
- 	^ type ifNotNil:
- 		[isPointerType
  			ifTrue: [type asPointerType "e.g. int* MyStruct* "]
  			ifFalse: [isNonPointerType
  				ifTrue: [type asNonPointerType "e.g. *IntPtr *MyStructPtr "]
  				ifFalse: [type "e.g. int IntPtr MyStruct MyStructPtr "]]]!

Item was changed:
  ----- Method: ExternalType>>isTypeAlias (in category 'testing') -----
  isTypeAlias
  	
+ 	self subclassResponsibility.!
- 	^true ifTrue: [false] ifFalse: [self subclassResponsibility]!

Item was removed:
- ----- Method: ExternalUnknownType>>readFieldAt: (in category 'external structure') -----
- readFieldAt: anInteger
- 	^'self error: ''cannot read field at ', anInteger printString, '; field has unknown type'''!

Item was removed:
- ----- Method: ExternalUnknownType>>writeFieldAt:with: (in category 'external structure') -----
- writeFieldAt: anInteger with: aString
- 	^'self error: ''cannot read field at ', anInteger printString, ' with name ', aString, '; field has unknown type'''!

Item was changed:
  MessageSend subclass: #FFIAtomicReadWriteSend
  	instanceVariableNames: 'byteSize'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'FFI-Kernel-Support'!
  
+ !FFIAtomicReadWriteSend commentStamp: 'mt 8/6/2021 16:16' prior: 0!
+ I am a message send for reading and writing atomic values from and to byte arrays or external addresses. I can be used for all direct mappings from atomic type to primitive send such as #float, #double, and #int32_t.
- !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 class>>basicFromType: (in category 'instance creation') -----
+ basicFromType: atomicType
+ 	
+ 	^(self lookupSelectorsFor: atomicType) collect:
+ 		[:selector| | arguments |
+ 		arguments := selector numArgs caseOf: {
+ 							[1] -> "e.g. doubleAt:"					[#(nil)]. "byteOffset"
+ 							[2] -> "e.g. floatAt:put:"				[#(nil nil)]. "byteOffset aFloat" }.
+ 		(self receiver: nil "handle" selector: selector arguments: arguments)
+ 			byteSize: atomicType byteSize;
+ 			yourself]!

Item was changed:
  ----- Method: FFIAtomicReadWriteSend class>>fromType: (in category 'instance creation') -----
  fromType: atomicType
- 
- 	atomicType isFloatType
- 		ifTrue: [^ FloatReadWriteSend fromType: atomicType].
  	
  	atomicType isIntegerType
+ 		ifTrue: [^ GenericIntegerReadWriteSend fromType: atomicType].
- 		ifTrue: [^ IntegerReadWriteSend fromType: atomicType].
  		
  	atomicType isCharType
+ 		ifTrue: [^ GenericCharacterReadWriteSend fromType: atomicType].
- 		ifTrue: [^ CharacterReadWriteSend fromType: atomicType].
  	
  	atomicType isBoolType
+ 		ifTrue: [^ GenericBooleanReadWriteSend fromType: atomicType].
- 		ifTrue: [^ BooleanReadWriteSend fromType: atomicType].
  		
  	atomicType isVoid
  		ifTrue: [^ VoidReadWriteSend fromType: atomicType].
+ 
+ 	^ self basicFromType: atomicType!
- 		
- 	self error: 'Unkown atomic type!!'.!

Item was changed:
  ----- Method: FFIAtomicReadWriteSend class>>lookupSelectorsFor: (in category 'instance creation') -----
  lookupSelectorsFor: atomicType
+ 
  	| result |
+ 	result := { nil. "read selector" nil. "write selector" }.
+ 	ByteArray methodsDo: [:method |
+ 		(method pragmaAt: #ffiAtomicRead:) ifNotNil: [:pragma |
+ 			(self pragma: pragma selectsAtomicType: atomicType)
+ 				ifTrue: [
+ 					result at: 1 put: method selector.
+ 					(result at: 2) ifNotNil: [^ result "early out"] ]].
+ 		(method pragmaAt: #ffiAtomicWrite:) ifNotNil: [:pragma |
+ 			(self pragma: pragma selectsAtomicType: atomicType)
+ 				ifTrue: [
+ 					result at: 2 put: method selector.
+ 					(result at: 1) ifNotNil: [^ result "early out"] ]] ].
- 	result := { nil. "read selector" nil "write selector" }.
- 	"Maybe these selectors should be cached in a couple of class variables?"
- 	(((ByteArray organization listAtCategoryNamed: #'*FFI-Kernel-accessing') sorted: [:s1 :s2| s1 numArgs <= s2 numArgs])
- 		collect: [:selector| ByteArray compiledMethodAt: selector])
- 		do: 	[:method |
- 			(self pragma: (method pragmaAt: #ffiAtomicRead:) selectsAtomicType: atomicType) ifTrue:
- 				[result at: 1 put: method selector.
- 				 (result at: 2) ifNotNil: [^result]].
- 			(self pragma: (method pragmaAt: #ffiAtomicWrite:) selectsAtomicType: atomicType) ifTrue:
- 				[result at: 2 put: method selector.
- 				 (result at: 1) ifNotNil: [^result]]].
  			
+ 	self notify: ('Could not find selectors for both reading and writing {1}!!' format: {atomicType typeName}).
+ 	^ result!
- 	self error: 'Could not find selectors for both read and write!!'.
- 	^result!

Item was changed:
  ----- Method: FFIAtomicReadWriteSend class>>pragma:selectsAtomicType: (in category 'instance creation') -----
+ pragma: pragma selectsAtomicType: atomicType
+ 
+ 	| typeNames |
+ 	typeNames := pragma argumentAt: 1.
+ 	typeNames isArray ifFalse: [typeNames := {typeNames}].
+ 	^ typeNames anySatisfy: [:typeName |
+ 		(ExternalType atomicTypeNamed: typeName) = atomicType]!
- pragma: pragmaOrNil selectsAtomicType: atomicType
- 	| pragmaLiteral |
- 	pragmaOrNil ifNil: [^false].
- 	pragmaLiteral := pragmaOrNil argumentAt: 1.
- 	pragmaLiteral isArray ifTrue:
- 		[^pragmaLiteral anySatisfy:
- 			[:typeName| (ExternalType atomicTypeNamed: typeName) = atomicType]].
- 	^(ExternalType atomicTypeNamed: pragmaLiteral) = atomicType!

Item was changed:
  ----- Method: FFIAtomicReadWriteSend>>handle:at: (in category 'evaluating') -----
  handle: receiver at: byteOffset
  	
+ 	^ receiver
+ 		perform: selector
+ 		with: byteOffset!
- 	self subclassResponsibility.!

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

Item was changed:
  ----- Method: FFIAtomicReadWriteSend>>isReading (in category 'accessing') -----
  isReading
  
+ 	^ selector numArgs = 1!
- 	self subclassResponsibility.!

Item was removed:
- ----- Method: Float32Array class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType float asArrayType: nil!

Item was added:
+ ----- Method: Float32Array>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType float!

Item was added:
+ ----- Method: Float32Array>>floatAt: (in category '*FFI-Kernel-accessing') -----
+ floatAt: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 	
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: Float32Array>>floatAt:put: (in category '*FFI-Kernel-accessing') -----
+ floatAt: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:put:."
+ 	
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: Float64Array class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType double asArrayType: nil!

Item was added:
+ ----- Method: Float64Array>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType double!

Item was added:
+ ----- Method: Float64Array>>doubleAt: (in category '*FFI-Kernel-accessing') -----
+ doubleAt: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: Float64Array>>doubleAt:put: (in category '*FFI-Kernel-accessing') -----
+ doubleAt: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:put:."
+ 	
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: FloatArray>>doubleAt: (in category '*FFI-Kernel-accessing') -----
- doubleAt: byteOffset
- 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
- 
- 	^ self atByteOffset: byteOffset!

Item was removed:
- ----- Method: FloatArray>>doubleAt:put: (in category '*FFI-Kernel-accessing') -----
- doubleAt: byteOffset put: value
- 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:put:."
- 	
- 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- FFIAtomicReadWriteSend subclass: #FloatReadWriteSend
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'FFI-Kernel-Support'!
- 
- !FloatReadWriteSend commentStamp: 'mt 5/19/2021 10:19' prior: 0!
- I am a message send for reading and writing atomic float values from and to byte arrays or external addresses. See #isFloatType and #initializeAtomicSends.!

Item was removed:
- ----- Method: FloatReadWriteSend class>>fromType: (in category 'instance creation') -----
- fromType: type
- 
- 	^(self lookupSelectorsFor: type) collect:
- 		[:selector| | arguments |
- 		arguments := selector numArgs caseOf: {
- 							[1] -> "e.g. doubleAt:"					[#(nil)]. "byteOffset"
- 							[2] -> "e.g. floatAt:put:"				[#(nil nil)]. "byteOffset aFloat" }.
- 		(self receiver: nil "handle" selector: selector arguments: arguments)
- 			byteSize: type byteSize;
- 			yourself]!

Item was removed:
- ----- Method: FloatReadWriteSend>>handle:at: (in category 'evaluating') -----
- handle: receiver at: byteOffset
- 	
- 	^ receiver
- 		perform: selector
- 		with: byteOffset!

Item was removed:
- ----- Method: FloatReadWriteSend>>handle:at:put: (in category 'evaluating') -----
- handle: receiver at: byteOffset put: floatValue
- 	
- 	receiver
- 		perform: selector
- 		with: byteOffset
- 		with: floatValue.
- 	^ floatValue!

Item was removed:
- ----- Method: FloatReadWriteSend>>isReading (in category 'accessing') -----
- isReading
- 
- 	^ selector numArgs = 1!

Item was added:
+ GenericIntegerReadWriteSend subclass: #GenericBooleanReadWriteSend
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Kernel-Support'!
+ 
+ !GenericBooleanReadWriteSend commentStamp: 'mt 5/19/2021 10:17' prior: 0!
+ I am a specialization for the atomic 'bool' type, which maps to 'byte' but adds extra pre- and post-processing to read and write instances of Boolean, i.e. true and false.!

Item was added:
+ ----- Method: GenericBooleanReadWriteSend class>>fromType: (in category 'instance creation') -----
+ fromType: type
+ 
+ 	^ super fromType: ExternalType byte!

Item was added:
+ ----- Method: GenericBooleanReadWriteSend class>>specificSendClass (in category 'instance creation') -----
+ specificSendClass
+ 
+ 	^ BooleanReadWriteSend!

Item was added:
+ ----- Method: GenericBooleanReadWriteSend>>handle:at: (in category 'evaluating') -----
+ handle: handle at: byteOffset
+ 
+ 	^ (super handle: handle at: byteOffset) ~= 0!

Item was added:
+ ----- Method: GenericBooleanReadWriteSend>>handle:at:put: (in category 'evaluating') -----
+ handle: handle at: byteOffset put: aBoolean
+ 
+ 	super
+ 		handle: handle
+ 		at: byteOffset
+ 		put: (aBoolean ifTrue: [1] ifFalse: [0]).
+ 	^ aBoolean!

Item was added:
+ ----- Method: GenericBooleanReadWriteSend>>template (in category 'compiling') -----
+ template
+ 
+ 	^ self isReading
+ 		ifTrue: ['(', super template, ') ~= 0']
+ 		ifFalse: [super template copyReplaceAll: '{3}' with: '({3} ifTrue: [1] ifFalse: [0])']!

Item was added:
+ GenericIntegerReadWriteSend subclass: #GenericCharacterReadWriteSend
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Kernel-Support'!
+ 
+ !GenericCharacterReadWriteSend commentStamp: 'mt 5/19/2021 10:18' prior: 0!
+ I am a specialization for the atomic 'char' and 'schar' types, which both map to (unsigned) 'byte' but add extra pre- and post-processing to read and write instances of Character such as $A and $Z.!

Item was added:
+ ----- Method: GenericCharacterReadWriteSend class>>fromType: (in category 'instance creation') -----
+ fromType: type
+ 
+ 	^ super fromType: ExternalType byte!

Item was added:
+ ----- Method: GenericCharacterReadWriteSend class>>specificSendClass (in category 'instance creation') -----
+ specificSendClass
+ 
+ 	^ CharacterReadWriteSend!

Item was added:
+ ----- Method: GenericCharacterReadWriteSend>>handle:at: (in category 'evaluating') -----
+ handle: handle at: byteOffset
+ 
+ 	^ (super handle: handle at: byteOffset) asCharacter!

Item was added:
+ ----- Method: GenericCharacterReadWriteSend>>handle:at:put: (in category 'evaluating') -----
+ handle: handle at: byteOffset put: aCharacter
+ 
+ 	super
+ 		handle: handle
+ 		at: byteOffset
+ 		put: aCharacter asciiValue.
+ 	^ aCharacter!

Item was added:
+ ----- Method: GenericCharacterReadWriteSend>>template (in category 'compiling') -----
+ template
+ 
+ 	^ self isReading
+ 		ifTrue: ['(', super template, ') asCharacter']
+ 		ifFalse: [super template copyReplaceAll: '{3}' with: '{3} asciiValue']!

Item was added:
+ FFIAtomicReadWriteSend subclass: #GenericIntegerReadWriteSend
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Kernel-Support'!
+ 
+ !GenericIntegerReadWriteSend commentStamp: 'mt 8/6/2021 16:11' prior: 0!
+ I am a message send for reading and writing atomic integer values from and to byte arrays or external addresses. My instances memoize type-specific #byteSize and #isSigned. See #isIntegerType and #initializeAtomicSends.
+ 
+ I am generic in the sense that my target primitive covers several atomic types.!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend class>>basicFromType: (in category 'instance creation') -----
+ basicFromType: type
+ 	"Overwritten to account for byteSize and isSigned."
+ 
+ 	^(self lookupSelectorsFor: type) collect:
+ 		[:selector| | arguments sendClass |
+ 		arguments := selector numArgs caseOf: {
+ 							[1] -> "e.g. int32At:"					[#(nil)]. "byteOffset"
+ 							[2] -> "e.g. int8At:put:"				[#(nil nil)]. "byteOffset integerValue"
+ 							[3] -> "e.g. integerAt:size:signed:"		[{nil. "byteOffset" type byteSize. type isSigned}]. 
+ 							[4] -> "e.g. integerAt:put:size:signed:"	[{nil. "byteOffset" nil. "integerValue" type byteSize. type isSigned}] }.
+ 		sendClass := selector numArgs > 2
+ 			ifTrue: [self "generic send-class"]
+ 			ifFalse: [self specificSendClass].
+ 		(sendClass receiver: nil "handle" selector: selector arguments: arguments)
+ 			byteSize: type byteSize;
+ 			yourself]!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend class>>fromType: (in category 'instance creation') -----
+ fromType: atomicType
+ 
+ 	^ self basicFromType: atomicType!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend class>>specificSendClass (in category 'instance creation') -----
+ specificSendClass
+ 	"Answer the send-class that should be used for direct mappings between atomic type and primitive send."
+ 	
+ 	^ FFIAtomicReadWriteSend!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend>>handle:at: (in category 'evaluating') -----
+ handle: receiver at: byteOffset
+ 	"Read."
+ 	
+ 	^arguments size = 1
+ 		ifTrue: [receiver perform: selector with: byteOffset]
+ 		ifFalse:
+ 			[receiver
+ 				perform: selector
+ 				with: byteOffset
+ 				with: (arguments at: 2) "byteSize"
+ 				with: (arguments at: 3)] "isSigned"!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend>>handle:at:put: (in category 'evaluating') -----
+ handle: receiver at: byteOffset put: integerValue
+ 	"Write."
+ 	arguments size = 2
+ 		ifTrue:
+ 			[receiver perform: selector with: byteOffset with: integerValue]
+ 		ifFalse:
+ 			[receiver
+ 				perform: selector
+ 				with: byteOffset
+ 				with: integerValue
+ 				with: (arguments at: 3) "byteSize"
+ 				with: (arguments at: 4)]. "isSigned"
+ 	^integerValue!

Item was added:
+ ----- Method: GenericIntegerReadWriteSend>>isReading (in category 'accessing') -----
+ isReading
+ 
+ 	^ selector numArgs = 3!

Item was removed:
- FFIAtomicReadWriteSend subclass: #IntegerReadWriteSend
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'FFI-Kernel-Support'!
- 
- !IntegerReadWriteSend commentStamp: 'mt 5/19/2021 10:15' prior: 0!
- I am a message send for reading and writing atomic integer values from and to byte arrays or external addresses. My instances memoize type-specific #byteSize and #isSigned. See #isIntegerType and #initializeAtomicSends.!

Item was removed:
- ----- Method: IntegerReadWriteSend class>>fromType: (in category 'instance creation') -----
- fromType: type
- 	"Overwritten to account for byteSize and isSigned."
- 
- 	^(self lookupSelectorsFor: type) collect:
- 		[:selector| | arguments |
- 		arguments := selector numArgs caseOf: {
- 							[1] -> "e.g. int32At:"					[#(nil)]. "byteOffset"
- 							[2] -> "e.g. int8At:put:"				[#(nil nil)]. "byteOffset integerValue"
- 							[3] -> "e.g. integerAt:size:signed:"		[{nil. "byteOffset" type byteSize. type isSigned}]. 
- 							[4] -> "e.g. integerAt:put:size:signed:"	[{nil. "byteOffset" nil. "integerValue" type byteSize. type isSigned}] }.
- 		(self receiver: nil "handle" selector: selector arguments: arguments)
- 			byteSize: type byteSize;
- 			yourself]!

Item was removed:
- ----- Method: IntegerReadWriteSend>>handle:at: (in category 'evaluating') -----
- handle: receiver at: byteOffset
- 	"Read."
- 	
- 	^arguments size = 1
- 		ifTrue: [receiver perform: selector with: byteOffset]
- 		ifFalse:
- 			[receiver
- 				perform: selector
- 				with: byteOffset
- 				with: (arguments at: 2) "byteSize"
- 				with: (arguments at: 3)] "isSigned"!

Item was removed:
- ----- Method: IntegerReadWriteSend>>handle:at:put: (in category 'evaluating') -----
- handle: receiver at: byteOffset put: integerValue
- 	"Write."
- 	arguments size = 2
- 		ifTrue:
- 			[receiver perform: selector with: byteOffset with: integerValue]
- 		ifFalse:
- 			[receiver
- 				perform: selector
- 				with: byteOffset
- 				with: integerValue
- 				with: (arguments at: 3) "byteSize"
- 				with: (arguments at: 4)]. "isSigned"
- 	^integerValue!

Item was removed:
- ----- Method: IntegerReadWriteSend>>isReading (in category 'accessing') -----
- isReading
- 
- 	^ selector numArgs = 3!

Item was changed:
  ----- Method: RawBitsArray class>>externalType (in category '*FFI-Kernel') -----
  externalType
  
+ 	^ self new contentType asArrayType: nil!
- 	self subclassResponsibility.!

Item was changed:
  ----- Method: RawBitsArray>>contentType (in category '*FFI-Kernel-external data') -----
  contentType
  
+ 	self subclassResponsibility.!
- 	^ self externalType contentType!

Item was changed:
  ----- Method: RawBitsArray>>externalType (in category '*FFI-Kernel-external data') -----
  externalType
  
+ 	^ self contentType asArrayType: self size!
- 	^ self class externalType contentType asArrayType: self size!

Item was removed:
- ----- Method: SignedByteArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType int8_t asArrayType: nil!

Item was added:
+ ----- Method: SignedByteArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType int8_t!

Item was added:
+ ----- Method: SignedByteArray>>int8At: (in category '*FFI-Kernel-accessing') -----
+ int8At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedByteArray>>int8At:put: (in category '*FFI-Kernel-accessing') -----
+ int8At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: SignedDoubleByteArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType int16_t asArrayType: nil!

Item was added:
+ ----- Method: SignedDoubleByteArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType int16_t!

Item was added:
+ ----- Method: SignedDoubleByteArray>>int16At: (in category '*FFI-Kernel-accessing') -----
+ int16At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedDoubleByteArray>>int16At:put: (in category '*FFI-Kernel-accessing') -----
+ int16At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: SignedDoubleWordArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType int64_t asArrayType: nil!

Item was added:
+ ----- Method: SignedDoubleWordArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType int64_t!

Item was added:
+ ----- Method: SignedDoubleWordArray>>int64At: (in category '*FFI-Kernel-accessing') -----
+ int64At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedDoubleWordArray>>int64At:put: (in category '*FFI-Kernel-accessing') -----
+ int64At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: SignedWordArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType int32_t asArrayType: nil!

Item was added:
+ ----- Method: SignedWordArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType int32_t!

Item was added:
+ ----- Method: SignedWordArray>>int32At: (in category '*FFI-Kernel-accessing') -----
+ int32At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedWordArray>>int32At:put: (in category '*FFI-Kernel-accessing') -----
+ int32At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was removed:
- ----- Method: WordArray class>>externalType (in category '*FFI-Kernel') -----
- externalType
- 
- 	^ ExternalType uint32_t asArrayType: nil!

Item was added:
+ ----- Method: WordArray>>contentType (in category '*FFI-Kernel-external data') -----
+ contentType
+ 
+ 	^ ExternalType uint32_t!

Item was added:
+ ----- Method: WordArray>>uint32At: (in category '*FFI-Kernel-accessing') -----
+ uint32At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: WordArray>>uint32At:put: (in category '*FFI-Kernel-accessing') -----
+ uint32At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was changed:
+ (PackageInfo named: 'FFI-Kernel') postscript: '"Reinitialize FFIAtomicReadWriteSend to use the new integer primitives"
+ ExternalType resetAllAtomicTypes.'!
- (PackageInfo named: 'FFI-Kernel') postscript: '"Reinitialize FFIAtomicReadWriteSend to use the new accessors"
- ExternalType initializeDefaultTypes'!



More information about the Squeak-dev mailing list