FFI: FFI-Kernel-mt.128.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

FFI: FFI-Kernel-mt.128.mcz

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

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

Name: FFI-Kernel-mt.128
Author: mt
Time: 4 May 2021, 12:22:47.736881 pm
UUID: b1af22ec-1c21-a544-82f7-af8466544ab9
Ancestors: FFI-Kernel-mt.127

Renames byte-array writer to read-writer because it can improve reading by avoiding intermediate copies.

Fixes and refactors #from:to: in ExternalData to support ByteArrayReadWriter by just re-using #structAt:length:, which works as expected on ByteArray and ExternalAddress.

Signal an exception when trying to instantiate external data without a type.

Adds some common accessors known from sequenceable collections to external data to help write more compact tests.

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

Item was changed:
  SystemOrganization addCategory: #'FFI-Kernel'!
+ SystemOrganization addCategory: #'FFI-Kernel-Support'!

Item was added:
+ ProtoObject subclass: #ByteArrayReadWriter
+ instanceVariableNames: 'byteOffset byteSize byteArray'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'FFI-Kernel-Support'!
+
+ !ByteArrayReadWriter 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: ByteArrayReadWriter class>>on: (in category 'instance creation') -----
+ on: handle
+ "Wraps the given handle into a read-writer. Avoid double-wrapping."
+
+ self assert: [handle isInternalMemory].
+
+ ^ (thisContext objectClass: handle) == self
+ ifTrue: [handle]
+ ifFalse: [self new setArray: handle]!

Item was added:
+ ----- Method: ByteArrayReadWriter>>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: ByteArrayReadWriter>>errorSubscriptBounds: (in category 'initialization') -----
+ errorSubscriptBounds: index
+
+ Error signal: 'subscript is out of bounds: ' , index printString.!

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

Item was added:
+ ----- Method: ByteArrayReadWriter>>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: ByteArrayReadWriter>>structAt:length: (in category 'accessing') -----
+ structAt: newByteOffset length: newLength
+
+ ^ ByteArrayReadWriter new
+ setArray: byteArray
+ offset: byteOffset + newByteOffset - 1
+ size: newLength!

Item was added:
+ ----- Method: ByteArrayReadWriter>>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 removed:
- 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 removed:
- ----- Method: ByteArrayWriter class>>on: (in category 'instance creation') -----
- on: handle
-
- self assert: [handle isInternalMemory].
- ^ self new setArray: handle!

Item was removed:
- ----- 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 removed:
- ----- Method: ByteArrayWriter>>errorSubscriptBounds: (in category 'initialization') -----
- errorSubscriptBounds: index
-
- Error signal: 'subscript is out of bounds: ' , index printString.!

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

Item was removed:
- ----- 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 removed:
- ----- Method: ByteArrayWriter>>structAt:length: (in category 'accessing') -----
- structAt: newByteOffset length: newLength
-
- ^ ByteArrayWriter new
- setArray: byteArray
- offset: byteOffset + newByteOffset - 1
- size: newLength!

Item was removed:
- ----- 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: ExternalData class>>fromHandle: (in category 'instance creation') -----
+ fromHandle: aHandle
+ "We need type information. See #fromHandle:type:"
+ self shouldNotImplement.!

Item was added:
+ ----- Method: ExternalData>>eighth (in category 'accessing - convenience') -----
+ eighth
+
+ ^ self at: 8!

Item was added:
+ ----- Method: ExternalData>>fifth (in category 'accessing - convenience') -----
+ fifth
+
+ ^ self at: 5!

Item was added:
+ ----- Method: ExternalData>>first (in category 'accessing - convenience') -----
+ first
+
+ ^ self at: 1!

Item was added:
+ ----- Method: ExternalData>>fourth (in category 'accessing - convenience') -----
+ fourth
+
+ ^ self at: 4!

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 newType |
  ((1 > firstIndex) or: [size notNil and: [lastIndex > size]])
  ifTrue: [^ self errorSubscriptBounds: lastIndex].
 
  byteOffset := ((firstIndex-1) * self contentType byteSize)+1.
+ numElements := lastIndex - firstIndex + 1 max: 0.
- numElements := lastIndex - firstIndex + 1.
  byteSize := numElements * self contentType byteSize.
 
  "For portions of a null-terminated C string, change the type from char* to byte* to avoid confusion."
  newType := self containerType = ExternalType string
  ifTrue: [ExternalType byte asPointerType]
  ifFalse: [self containerType "No change"].
 
+ ^ (ExternalData
+ fromHandle: (handle structAt: byteOffset length: byteSize)
+ type: newType) size: numElements; yourself!
- ^ lastIndex < firstIndex
- ifTrue: [
- handle isExternalAddress
- ifTrue: [(ExternalData
- fromHandle: handle + (byteOffset - 1) "Keep pointer."
- type: newType) size: 0; yourself]
- ifFalse: [(ExternalData
- fromHandle: #[] "Empty memory"
- type: newType) size: 0; yourself]]
- ifFalse: [
- handle isExternalAddress
- ifTrue: [(ExternalData
- fromHandle: handle + (byteOffset - 1)
- type: newType) size: numElements; yourself]
- ifFalse: [(ExternalData
- fromHandle: (handle copyFrom: byteOffset to: byteOffset+byteSize-1)
- type: newType) size: numElements; yourself]]!

Item was added:
+ ----- Method: ExternalData>>ninth (in category 'accessing - convenience') -----
+ ninth
+
+ ^ self at: 9!

Item was added:
+ ----- Method: ExternalData>>second (in category 'accessing - convenience') -----
+ second
+
+ ^ self at: 2!

Item was added:
+ ----- Method: ExternalData>>seventh (in category 'accessing - convenience') -----
+ seventh
+
+ ^ self at: 7!

Item was added:
+ ----- Method: ExternalData>>sixth (in category 'accessing - convenience') -----
+ sixth
+
+ ^ self at: 6!

Item was added:
+ ----- Method: ExternalData>>third (in category 'accessing - convenience') -----
+ third
+
+ ^ self at: 3!

Item was added:
+ ----- Method: ExternalData>>writer (in category 'accessing') -----
+ writer
+ "Overwritten to preserve type and size."
+ handle isInternalMemory ifFalse: [^ self].
+
+ ^ (self class
+ fromHandle: (ByteArrayReadWriter on: handle)
+ type: type) size: size; yourself!

Item was added:
+ ----- Method: ExternalStructure>>reader (in category 'accessing') -----
+ reader
+
+ ^ self writer!

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