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

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Mon Jun 22 08:27:51 UTC 2020


No, no,
throw that code away, and have a look at  in VMMakerInbox, you will
understand better...

In fact, if you read my proposals, I'd like to get rid of FFIFlagStructure
altogether...
Either a type is atomic or composite, it's not both nor neither...
So we ain't gonna need 2 flags FFIFlagAtomic and FFIFlagStructure.

So hopefully, we shall throw away the FFIFlagStructure and make your life
easier at image side :)

Le lun. 22 juin 2020 à 10:19, Marcel Taeumel <marcel.taeumel at hpi.de> a
écrit :

> Hi Nicolas,
>
> sure, there might be a difference. But you have all the information you
> need directly in the plugin already:
>
>
>
> Let me catch up on this later this week.
>
> Best,
> Marcel
>
> Am 22.06.2020 09:56:05 schrieb Nicolas Cellier <
> nicolas.cellier.aka.nice at gmail.com>:
> Hi Marcel,
> So you mean that I don't really need to distinguish pointer to struct and
> pointer to atomic type alias?
> Maybe...
>
> There is currently a difference:
> - an atomic type alias has an immediate value as handle
>   it thus cannot be passed as parameter by reference
>   (well, for aliases to pointers, I don't really know...)
> - a struct has a memory zone as value (ExternalAddress or direct ByteArray)
>  it thus can be passed as parameter by reference without having to resort
> to an ExternalData.
> See ffiPassStructureArgumentByReference: oop Class: oopClass
> expectedClass: argClass In: calloutState
> vs ffiPassAtomicArgumentByReference: oop Class: oopClass expectedClass:
> argClass In: calloutState
>
>
> Le lun. 22 juin 2020 à 09:18, Marcel Taeumel <marcel.taeumel at hpi.de> a
> écrit :
>
>> Hi Nicolas,
>>
>> thanks! :-) I will take a look at it during this week, I hope.
>>
>> Here is a first thought:
>>
>> I don't think that the pointer types for external structs should have the
>> FFIFlagStructure."referentClass" should be more than enough for the FFI
>> plugin side for both coercing and return-value packaging.
>>
>> So, -1 for now but maybe I overlooked a use case. Raising this
>> FFIFlagStructure here for such pointer types really messes up a lot of my
>> current conceptual model about the relationship of ExternalStructure and
>> ExternalType/ExternalStructureType. :-)
>>
>> Why is "referentClass" not enough for the plugin side? Just check for
>> ifNil, if not, instantiate and put instVar 0 to the return value. Done. ;-)
>> For coercing, just compare argument class with "referentClass" in the
>> argType; then check for the pointer flag. Maybe discriminate between
>> ByteArray and ExternalAddress.
>>
>> ...please don't raise FFIFlagStructure for pointer types for external
>> structures... pretty please ^__^
>>
>> Best,
>> Marcel
>>
>> Am 21.06.2020 22:34:09 schrieb commits at source.squeak.org <
>> commits at source.squeak.org>:
>> 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].!
>>
>>
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200622/b63c3209/attachment-0001.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: image.png
Type: image/png
Size: 118657 bytes
Desc: not available
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200622/b63c3209/attachment-0001.png>


More information about the Squeak-dev mailing list