FFI: FFI-Kernel-mt.140.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.140.mcz

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

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

Name: FFI-Kernel-mt.140
Author: mt
Time: 7 May 2021, 11:54:20.790725 am
UUID: 417350cb-800d-de4a-9554-5e2398442674
Ancestors: FFI-Kernel-mt.139

Refactors and clarifies the current state of container types and content types.

Browse all senders of #contentVsContainer to learn about the current trade-offs. Most of them are confined within ExternalData and ExternalArrayType, with two assertions in ExternalType.

Here is the current list of senders for #contentVsContainer:

ExternalData >> containerType
ExternalData >> contentType
ExternalData >> externalType
ExternalData >> pointerAt:
ExternalData >> pointerAt:put:
ExternalData >> setSize:
ExternalData >> setType:

ExternalArrayType >> allocate:
ExternalArrayType >> allocateExternal:
ExternalArrayType >> contentType
ExternalArrayType class >> newTypeForContentType:size:

ExternalType >> allocate:
ExternalType >> allocateExternal:

***

Luckily, I was able to get rid of ExternalStructure >> #byteSize and ExternalType >> #contentType again. :-) The latter being only defined for ExternalArrayType for now. The former can be replaced through "externalType byteSize" ... not sure whether a convenience accessor brings benefit here.

***

Note that for multi-dimensional container support we would have to make changes to the compiledSpec's design in types, which would also imply changes in the FFI plugin.

My current goal is to clean up what we have now, make an FFI release, and then go on brainstorming with Nicholas and Eliot and all other interested parties about possible next steps to support char** and int[10][20] and what-not. :-)

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

Item was changed:
  ----- Method: ExternalArrayType class>>newTypeForContentType:size: (in category 'instance creation') -----
  newTypeForContentType: contentType size: numElements
  "!!!!!! Be aware that only the pointer type can be used in calls. As of SqueakFFIPrims VMMaker.oscog-eem.2950, there is no actual support for array types in the FFI plugin !!!!!!"
 
  | type pointerType headerWord byteSize |
  self
+ flag: #contentVsContainer;
+ assert: [contentType isPointerType not and: [contentType isArrayType not]]
+ description: 'No support for multi-dimensional containers yet!!'.
- assert: [contentType isPointerType not]
- description: 'No support for pointers as content type yet!!'.
 
  self
  assert: [numElements > 0]
  description: 'Empty array types are not supported!!'.
 
  self
  assert: [contentType byteSize > 0]
  description: 'Invalid byte size!!'.
 
  self
  assert: [(ArrayTypes includesKey: contentType typeName -> numElements) not]
  description: 'Array type already exists. Use #typeNamed: to access it.'.
 
  type := self "ExternalArrayType" basicNew.
  pointerType := ExternalType basicNew.
 
  "1) Regular type"
  byteSize := numElements * contentType byteSize.
  self assert: [byteSize <= FFIStructSizeMask].
  headerWord := contentType headerWord.
  headerWord := headerWord bitClear: FFIStructSizeMask.
  headerWord := headerWord bitOr: byteSize.
  type
  setReferencedType: pointerType;
  compiledSpec: (WordArray with: headerWord);
  byteAlignment: contentType byteAlignment;
  setReferentClass: contentType referentClass;
  setSize: numElements.
 
  "2) Pointer type. Reuse the compiledSpec of the content-type's pointer type."
  pointerType
  setReferencedType: type;
  compiledSpec: contentType asPointerType compiledSpec copy;
  byteAlignment: contentType asPointerType byteAlignment;
  setReferentClass: contentType asPointerType referentClass.
 
  "3) Remember this new array type."
  ArrayTypes
  at: contentType typeName -> numElements
  put: type.
 
  ^ type!

Item was changed:
  ----- Method: ExternalArrayType>>allocate: (in category 'external data') -----
  allocate: anInteger
  "No support for n-dimensional containers."
+
+ self flag: #contentVsContainer.
  self notYetImplemented.!

Item was changed:
  ----- Method: ExternalArrayType>>allocateExternal: (in category 'external data') -----
  allocateExternal: anInteger
  "No support for n-dimensional containers."
+
+ self flag: #contentVsContainer.
  self notYetImplemented.!

Item was changed:
  ----- Method: ExternalArrayType>>contentType (in category 'external data') -----
+ contentType "^ <ExternalType>"
+ "We are an array of things. Our content type is encoded in the compiledSpec's headerWord. The super implementation of #typeName can figure that out."
- contentType
- "Overwritten because array types have their content type as part of their non-pointer type."
 
+ self flag: #contentVsContainer. "mt: For n-dimensional containers, we might have to adapt this."
  ^ ExternalType typeNamed: super typeName!

Item was changed:
  ----- Method: ExternalArrayType>>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:."
 
  self checkType.
 
+ ^ ExternalData
- ^ (ExternalData
  fromHandle: (handle structAt: byteOffset length: self byteSize)
+ type: self!
- type: self contentType) size: self size; yourself!

Item was changed:
  ----- Method: ExternalArrayType>>readFieldAt: (in category 'external structure') -----
  readFieldAt: byteOffset
  "Answer a string defining the accessor to an entity of the receiver type starting at the given byte offset.
  Private. Used for field definition only."
 
  self checkType.
 
  ^ String streamContents:[:s |
+ s nextPutAll:'^ ExternalData fromHandle: (handle structAt: ';
- s nextPutAll:'^ (ExternalData fromHandle: (handle structAt: ';
  print: byteOffset;
  nextPutAll: ' length: ';
  print: self byteSize;
  nextPutAll: ') type: '.
 
  self contentType isAtomic
  ifTrue: [s nextPutAll: 'ExternalType ', self contentType typeName]
  ifFalse: [s nextPutAll: self contentType typeName, ' externalType'].
 
+ s nextPutAll: ' size: '; print: self size]!
- s nextPutAll: ') size: '; print: self size; nextPutAll: '; yourself']!

Item was changed:
  ----- Method: ExternalData class>>fromHandle:type: (in category 'instance creation') -----
+ fromHandle: aHandle type: containerType
+
+ ^ self basicNew setHandle: aHandle type: containerType!
- fromHandle: aHandle type: aType
- "Create a pointer to the given type"
- "ExternalData fromHandle: ExternalAddress new type: ExternalType float"
- ^self basicNew setHandle: aHandle type: aType!

Item was added:
+ ----- Method: ExternalData class>>fromHandle:type:size: (in category 'instance creation') -----
+ fromHandle: aHandle type: contentType size: numElements
+
+ ^ self basicNew setHandle: aHandle type: contentType size: numElements!

Item was changed:
  ----- Method: ExternalData>>byteSize (in category 'accessing') -----
  byteSize
  "Answer how many bytes the receiver manages."
 
  self sizeCheck.
+ ^ self size * self contentType byteSize!
-
- ^ handle isExternalAddress
- ifTrue: [self size * self contentType byteSize]
- ifFalse: [ "ByteArray" handle size]!

Item was changed:
  ----- Method: ExternalData>>containerType (in category 'accessing - types') -----
+ containerType "^ <ExternalType | #undefined >"
+ "Answer the current containter type. Note that pointer types with unknown size cannot serve as container type."
+
+ ^ size isNil
+ ifTrue: [
+ self flag: #contentVsContainer. "mt: Maybe we should have an actual type for this kind of container?"
+ self assert: [type isPointerType].
+ #undefined]
+ ifFalse: [
+ self assert: [type asNonPointerType isArrayType].
+ type asNonPointerType]!
- containerType
-
- ^ (size isNil or: [type isVoid])
- ifTrue: [type]
- ifFalse: [self contentType asArrayType: size]!

Item was changed:
  ----- Method: ExternalData>>contentType (in category 'accessing - types') -----
+ contentType "^ <ExternalType>"
+ "Answer the content type for the current container type. Handle the special case for pointer types with an unknown number of elements (i.e. #size)."
- contentType
 
+ | containerType contentType |
+ containerType := self containerType.
+
+ containerType = #undefined
+ flag: #contentVsContainer; "mt: Our best guess is the non-pointer type."
+ assert: [type isPointerType];
+ ifTrue: [
+ (contentType := type asNonPointerType) isArrayType
+ flag: #initializationOnly; "mt: We are in the middle of initializing this external data. See #setType and #setSize: to learn more."
+ ifTrue: [contentType := contentType contentType]]
+ ifFalse: [
+ contentType := containerType contentType].
+
+ ^ contentType!
- ^ type 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."
+
+ | result |
+ ^ (result := self containerType) = #undefined
+ ifFalse: [result]
+ ifTrue: [
+ self flag: #contentVsContainer. "mt: Avoid leaking #undefined to the outside."
+ ExternalType void]!
- externalType
-
- ^ 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 |
- | byteOffset numElements byteSize newType |
  ((1 > firstIndex) or: [size notNil and: [lastIndex > size]])
  ifTrue: [^ self errorSubscriptBounds: lastIndex].
 
+ contentType := self contentType.
+ byteOffset := ((firstIndex-1) * contentType byteSize)+1.
- byteOffset := ((firstIndex-1) * self contentType byteSize)+1.
  numElements := lastIndex - firstIndex + 1 max: 0.
+ byteSize := numElements * contentType byteSize.
- 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
- ^ (ExternalData
  fromHandle: (handle structAt: byteOffset length: byteSize)
+ type: contentType
+ size: numElements!
- type: newType) size: numElements; yourself!

Item was changed:
  ----- Method: ExternalData>>getExternalData (in category 'accessing - external structures') -----
  getExternalData
+ "Reads all bytes into object memory. Note that this does not flatten all bytes into a single array by repeatedly calling it. Also note that this does only work for an external address. It does not copy what's already in object memory. Use #copy if you want to get a another copy in the object memory. Also see ExternalStructure >> #postCopy."
- "Reads all bytes into object memory. Note that this does not flatten all bytes into a single array by repeatedly calling it. It does just work once for an external address."
 
  | data |
  handle isExternalAddress ifFalse: [^ self].
- self sizeCheck.
 
+ data := ByteArray new: self byteSize.
- data := ByteArray new: size * self contentType byteSize.
  1 to: data size do: [:index |
  data unsignedByteAt: index put: (handle unsignedByteAt: index)].
 
+ ^ ExternalData
- ^ (ExternalData
  fromHandle: data
+ type: type
+ size: size!
- type: self contentType)
- size: size!

Item was changed:
  ----- Method: ExternalData>>setHandle:type: (in category 'private') -----
+ setHandle: aHandle type: containerType
+
+ self setHandle: aHandle.
+ self setType: containerType.!
- setHandle: aHandle type: aType
- handle := aHandle.
- type := aType asPointerType.!

Item was added:
+ ----- Method: ExternalData>>setHandle:type:size: (in category 'private') -----
+ setHandle: aHandle type: contentType size: numElements
+
+ self setHandle: aHandle.
+ self setType: contentType.
+ self setSize: numElements.!

Item was added:
+ ----- Method: ExternalData>>setSize: (in category 'private') -----
+ setSize: numElements
+ "Set the size for the receiver, which will be used when enumerating its elements."
+
+ | ct |
+ ct := self contentType.
+ size := numElements.
+
+ self flag: #contentVsContainer. "mt: If we have a size, change the array type. If not, just hold on to the pointer type of the prior content type."
+ size
+ ifNil: [type := ct asPointerType]
+ ifNotNil: [type := (ct asArrayType: size) asPointerType].!

Item was added:
+ ----- Method: ExternalData>>setType: (in category 'private') -----
+ setType: contentOrContainerType
+ "Private. Set the type used to derive content and container types. If we get an array type, also remember its size to distinguish its pointer type from other pointer types."
+
+ type := contentOrContainerType asPointerType.
+
+ contentOrContainerType isArrayType ifTrue: [
+ self flag: #contentVsContainer. "mt: Note that we do not have to check whether the argument is actually the pointer type for an array type because those will usually be supplied with an extra call to #setSize: from the outside. See senders of #fromHandle:type:size:."
+ self setSize: contentOrContainerType size].!

Item was removed:
- ----- Method: ExternalData>>size: (in category 'accessing') -----
- size: anInteger
- "Set the size for the receiver, which will be used when enumerating its elements."
-
- size := anInteger.
- !

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

Item was changed:
  ----- Method: ExternalStructure>>asExternalData (in category 'converting') -----
  asExternalData
 
+ ^ ExternalData
+ fromHandle: self getHandle
+ type: self externalType "content type"
+ size: 1!
- ^ (ExternalData fromHandle: self getHandle type: self externalType)
- size: 1; yourself!

Item was removed:
- ----- Method: ExternalStructure>>byteSize (in category 'accessing') -----
- byteSize
- "Answer the number of bytes managed by the receiver."
-
- ^ self externalType byteSize!

Item was changed:
  ----- Method: ExternalStructureType>>storeOn: (in category 'printing') -----
  storeOn: aStream
 
  referentClass ifNil: [
  "unknown struct type"
  ^ aStream nextPutAll: 'nil'].
 
  aStream
  nextPut: $(;
  nextPutAll: ExternalType name; space;
  nextPutAll: #structTypeNamed:; space;
  store: referentClass name;
+ nextPut: $).!
- nextPut: $).
-
- self isPointerType ifTrue: [
- aStream space; nextPutAll: #asPointerType].!

Item was changed:
  ----- Method: ExternalType>>allocate: (in category 'external data') -----
  allocate: numElements
  "Allocate space for containing an array of numElements of this dataType"
 
  | handle |
  self
+ flag: #contentVsContainer;
  assert: [self isPointerType not or: [self isVoid]]
  description: 'No support for n-dimensional containers. Allocate for void* as workaround.';
  assert: [self byteSize > 0]
  description: 'Invalid byte size.'.
 
  handle := ByteArray new: self byteSize * numElements.
+ ^ExternalData fromHandle: handle type: self size: numElements!
- ^(ExternalData fromHandle: handle type: self) size: numElements!

Item was changed:
  ----- Method: ExternalType>>allocateExternal: (in category 'external data') -----
  allocateExternal: numElements
  "Allocate space for containing an array of numElements of this type. Note that we zero the memory for safe use. If you do not need that, please use ExternalAddress class >> #allocate: directly. BE AWARE that structs can have pointers tools automatically follow and thus risking a SEGFAULT and hence VM CRASH for uninitalized memory."
 
  | handle |
  self
+ flag: #contentVsContainer;
  assert: [self isPointerType not or: [self isVoid]]
  description: 'No support for n-dimensional containers. Allocate for void* as workaround.';
  assert: [self byteSize > 0]
  description: 'Invalid byte size.'.
 
  handle := ExternalAddress allocate: self byteSize * numElements.
+ ^(ExternalData fromHandle: handle type: self size: numElements)
- ^(ExternalData fromHandle: handle type: self)
- size: numElements;
  zeroMemory;
  yourself!

Item was removed:
- ----- Method: ExternalType>>contentType (in category 'external data') -----
- contentType
-
- | result |
- self
- assert: [self isPointerType]
- description: 'Content type is only defined for pointer types!!'.
-
- result := self asNonPointerType.
- ^ result isArrayType
- ifTrue: [result contentType]
- ifFalse: [result]!

Item was changed:
  (PackageInfo named: 'FFI-Kernel') postscript: 'Smalltalk removeFromStartUpList: ExternalAddress.
  Smalltalk removeFromStartUpList: ExternalObject.
 
  "Adds housekeeping for array types."
+ ExternalType resetAllStructureTypes.
- ExternalType resetAllStructureTypes..
 
+ "Re-generate all field accessors because in ExternalData, #size: was replaced with #setSet: and a new constructors for content and container types."
- "Re-generate all field accessors because type checks are now controlled by a new preference."
  ExternalStructure defineAllFields.
  '!