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

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

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

Name: FFI-Kernel-mt.146
Author: mt
Time: 15 May 2021, 2:56:07.781282 pm
UUID: c2bb685d-0aa5-384b-bd1c-3176fee51f46
Ancestors: FFI-Kernel-mt.145

Found a way to fix the handle for alias-to-pointer types. See #pointerAliasSpec for an explanation. Removes #checkHandle(Undo) because it is no longer needed.

Makes #isTypeAlias for atomic types and pointer types independent from the headerWord. This in turn makes #becomeKnownType more robust.

Clarify #setType: vs. #setContentType: in external data. Adds #asContentType: and #asType:size: besides #asType:. Removes those other #as* selectors because not needed -- use #first or #value.

Adds more comments.

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

Item was changed:
  ByteArray variableByteSubclass: #ExternalAddress
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
+ category: 'FFI-Kernel-Support'!
- category: 'FFI-Kernel'!
 
  !ExternalAddress commentStamp: '<historical>' prior: 0!
  An ExternalAddress is an opaque handle to objects outside Smalltalk memory (e.g., a pointer).!

Item was removed:
- ----- Method: ExternalAddress class>>fromByteArray: (in category 'instance creation') -----
- fromByteArray: aByteArray
-
- self flag: #pointerAliasCompatibility. "mt: Bug in FFI plugin, which fails to answer ExternalAddress as handle for alias-to-pointer types."
- self assert: [aByteArray size = ExternalAddress wordSize].
- ^ aByteArray changeClassTo: self!

Item was changed:
  ----- Method: ExternalData class>>fromHandle:type: (in category 'instance creation') -----
+ fromHandle: aHandle type: containerOrContentType
+ "Answer with given container type or content type and unknown size."
+
+ ^ self basicNew setHandle: aHandle type: containerOrContentType!
- fromHandle: aHandle type: containerType
-
- ^ self basicNew setHandle: aHandle type: containerType!

Item was added:
+ ----- Method: ExternalData>>asContentType: (in category 'converting') -----
+ asContentType: contentType
+ "Keep the size."
+
+ ^ ExternalData fromHandle: handle type: contentType size: self size!

Item was removed:
- ----- Method: ExternalData>>asExternalData (in category 'converting') -----
- asExternalData
-
- ^ self!

Item was removed:
- ----- Method: ExternalData>>asExternalStructure (in category 'converting') -----
- asExternalStructure
-
- self
- assert: [self contentType referentClass includesBehavior: ExternalStructure]
- description: 'Wrong type'.
-
- ^ self contentType referentClass fromHandle: handle!

Item was removed:
- ----- Method: ExternalData>>asExternalUnion (in category 'converting') -----
- asExternalUnion
-
- self
- assert: [self contentType referentClass includesBehavior: ExternalUnion]
- description: 'Wrong type'.
-
- ^ self contentType referentClass fromHandle: handle!

Item was changed:
  ----- Method: ExternalData>>asType: (in category 'converting') -----
+ asType: containerType
- asType: anExternalType
 
+ ^ ExternalData fromHandle: handle type: containerType!
- ^ ExternalData fromHandle: handle type: anExternalType!

Item was added:
+ ----- Method: ExternalData>>asType:size: (in category 'converting') -----
+ asType: contentType size: numElements
+
+ ^ ExternalData fromHandle: handle type: contentType size: numElements!

Item was removed:
- ----- Method: ExternalData>>checkHandle (in category 'compatibility') -----
- checkHandle
- "Not needed here."!

Item was changed:
  ----- Method: ExternalData>>containerType (in category 'accessing - types') -----
  containerType "^ <ExternalArrayType>"
  "Answer the current container type, which may or may not have a known #size and #byteSize."
 
+ self typeCheck.
- "Check type. If you happen to have a regular pointer type here, convert it into array type of unknown size. This can happen for result values of FFI calls."
- type asNonPointerType isArrayType
- ifFalse: [self setType: type].
-
  ^ type!

Item was changed:
+ ----- Method: ExternalData>>fromCString (in category 'accessing - unsafe') -----
- ----- Method: ExternalData>>fromCString (in category 'converting - support') -----
  fromCString
  "Read a NUL-terminated string"
 
  self
  assert: [self mightBeCString]
  description: 'Wrong content type'.
 
  ^ String streamContents: [:stream |
  self
  detect: [:char |
  char == Character null ifTrue: [true] ifFalse: [
  stream nextPut: char.
  false]]
  ifFound: [:char | "finished"]]!

Item was changed:
+ ----- Method: ExternalData>>fromCStrings (in category 'accessing - unsafe') -----
- ----- Method: ExternalData>>fromCStrings (in category 'converting - support') -----
  fromCStrings
  "Read a list of double-null terminated strings.
 
  https://devblogs.microsoft.com/oldnewthing/20110511-00/?p=10693
  http://web.archive.org/web/20100103003417/http://blogs.msdn.com/oldnewthing/archive/2009/10/08/9904646.aspx"
 
  self
  assert: [self mightBeCString]
  description: 'Wrong content type'.
 
  ^ Array streamContents: [:list | String streamContents: [:element |
  | lastChar |
  lastChar := nil.
  self
  detect: [:char |
  (lastChar == Character null and: [char == Character null])
  ifTrue: [true] ifFalse: [
  char == Character null
  ifTrue: [
  list nextPut: element contents.
  element reset]
  ifFalse: [
  element nextPut: char].
  lastChar := char. false]]
  ifFound: [:char | "finished"]]].!

Item was changed:
  ----- Method: ExternalData>>mightBeCString (in category 'testing') -----
  mightBeCString
 
  ^ self contentType = ExternalType char and: [self size isNil]!

Item was changed:
  ----- Method: ExternalData>>postCopy (in category 'copying') -----
  postCopy
  "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."
 
  | bytes |
  handle isExternalAddress ifFalse: [^ self].
  self sizeCheck.
 
  bytes := ByteArray new: self byteSize.
  1 to: bytes size do: [:index |
  bytes basicAt: index put: (handle unsignedByteAt: index)].
 
  handle := bytes.
+ self setType: type. "Change container type from pointer to non-pointer type."!
- self setType: type.!

Item was changed:
+ ----- Method: ExternalData>>setContentType: (in category 'initialize-release') -----
- ----- Method: ExternalData>>setContentType: (in category 'private') -----
  setContentType: externalType
 
  self setType: (externalType asArrayType: self size).!

Item was changed:
+ ----- Method: ExternalData>>setSize: (in category 'initialize-release') -----
- ----- Method: ExternalData>>setSize: (in category 'private') -----
  setSize: numElements
  "Set the size for the receiver, which will be used when enumerating its elements."
 
  self setType: (self contentType asArrayType: numElements).!

Item was changed:
  ----- Method: ExternalData>>setType: (in category 'private') -----
  setType: externalType
+ "Private. Set the type used to derive content and container types. If you want to change the content type later, use #setContentType:."
- "Private. Set the type used to derive content and container types."
 
  externalType isVoid ifTrue: [
  ^ self setType: externalType asPointerType].
 
  externalType asNonPointerType isArrayType
  ifTrue: [type := externalType]
  ifFalse: [type := (externalType asArrayType: nil)].
 
  handle isExternalAddress
  ifTrue: [type := type asPointerType]
  ifFalse: [type := type asNonPointerType].!

Item was added:
+ ----- Method: ExternalData>>typeCheck (in category 'private') -----
+ typeCheck
+ "Check type. If you happen to have a regular pointer type here, convert it into array type of unknown size. This can happen for result values of FFI calls if the signature did not specify, e.g., 'int[]' but 'int*'."
+
+ type asNonPointerType isArrayType
+ ifFalse: [self setType: type].!

Item was changed:
  ----- Method: ExternalObject>>ffiIdentical: (in category 'comparing') -----
  ffiIdentical: other
  "Define identity for external objects. External objects sharing an external address are considered 'externally identical.' "
 
  self == other ifTrue: [^ true].
  other isExternalObject ifFalse: [^ false].
  self getHandle species = other getHandle species ifFalse: [^ false].
 
  ^ (self getHandle ffiIdentical: other getHandle) or: [
- self checkHandle. other checkHandle.
  self getHandle isExternalAddress
  and: [other getHandle isExternalAddress]
  and: [self getHandle = other getHandle]]!

Item was changed:
  ----- Method: ExternalPointerType>>isTypeAlias (in category 'testing') -----
  isTypeAlias
 
+ ^ referentClass notNil
+ and: [referentClass isTypeAlias
+ and: [referentClass originalType isPointerType]]!
- ^ self headerWord allMask: ExternalType pointerAliasSpec!

Item was changed:
  ----- Method: ExternalPointerType>>readAlias (in category 'external structure') -----
  readAlias
  "
  ExternalStructure defineAllFields.
  "
+ ^ '^ {1} fromHandle: handle{2}' withCRs
- ^ 'self checkHandle. "Fix bug in FFI plugin."\ ^ {1} fromHandle: handle{2}' withCRs
  format: {
  (referentClass ifNil: [ExternalData]) name.
  referentClass ifNotNil: [''] ifNil: [
  ' type: ', self asNonPointerType "content type" storeString]}!

Item was removed:
- ----- Method: ExternalStructure>>checkHandle (in category 'compatibility') -----
- checkHandle
-
- | type |
- handle ifNil: [^ self "already free'd"].
- handle isExternalAddress ifTrue: [^ self "already ok"].
-
- type := self class externalType.
- self flag: #pointerAliasCompatibility. "mt: Bug in FFI plugin, which fails to answer ExternalAddress as handle for alias-to-pointer types."
-
- (type isPointerType and: [type isTypeAlias
- and: [handle size = ExternalAddress wordSize]]) ifTrue: [
- handle := ExternalAddress fromByteArray: handle].!

Item was removed:
- ----- Method: ExternalStructure>>checkHandleUndo (in category 'compatibility') -----
- checkHandleUndo
- "See #checkHandle. Call this if the FFI call would not work with the ExternalAddress."
-
- | type |
- self flag: #pointerAliasCompatibility.
-
- handle ifNil: [^ self "already free'd"].
- handle isInternalMemory ifTrue: [^ self "already ok"].
-
- type := self class externalType.
- (type isPointerType and: [type isTypeAlias
- and: [handle size = ExternalAddress wordSize]]) ifTrue: [
- handle := handle changeClassTo: ByteArray].!

Item was changed:
  ----- Method: ExternalStructure>>externalType (in category 'accessing') -----
  externalType
 
- self checkHandle. "Fix bug in FFI plugin."
  ^ handle isExternalAddress
  ifTrue: [self class externalType asPointerType]
  ifFalse: [self class externalType asNonPointerType]!

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

Item was changed:
  ----- Method: ExternalType class>>pointerAliasSpec (in category 'private') -----
  pointerAliasSpec
+ "Answers a mask to check the #headerWord for a type alias to a pointer type.
+
+ mt 5/15/2021 -- I removed the FFIFlagStructure because the FFI plugin returned byte arrays as pointers instead of an external address, which is really cumbersome to manage in the image. Also this distinction is not needed, which makes me believe it was a simple bug. -- Also note that simply converting thos byte arrays into external addresses in the image would not work for FFI calls, which actually expected those byte arrays. Strange. There might be some extra table managed for those. Still not sure why."
+ ^ "self structureSpec bitOr:" self pointerSpec!
- "Answers a mask to check the #headerWord for a type alias to a pointer type."
- ^ self structureSpec bitOr: self pointerSpec!

Item was changed:
  ----- Method: ExternalUnknownType>>becomeKnownType (in category 'construction') -----
  becomeKnownType
+ "Give me some purpose. :-)"
- "Give me some purpose. :-) The order of checks matters because some tests only look at the #headerWord. Make the tests that look into referentClass first."
 
+ self isTypeAliasForAtomic
+ ifTrue: [^ self becomeAtomicType].
+ self isTypeAliasForPointer
+ ifTrue: [^ self becomePointerType].
  self isTypeAliasForStructure
  ifTrue: [^ self becomeStructureType].
  self isTypeAliasForArray
  ifTrue: [^ self becomeArrayType].
 
- self isTypeAliasForAtomic
- ifTrue: [^ self becomeAtomicType].
- self isTypeAliasForPointer
- ifTrue: [^ self becomePointerType].
-
  ^ self becomeStructureType!

Item was changed:
  ----- Method: ExternalUnknownType>>isTypeAliasForAtomic (in category 'testing - type alias') -----
  isTypeAliasForAtomic
 
+ ^ referentClass notNil
+ and: [referentClass isTypeAlias
+ and: [referentClass originalType isAtomic]]!
- ^ self headerWord allMask: FFIFlagAtomic!

Item was changed:
  ----- Method: ExternalUnknownType>>isTypeAliasForPointer (in category 'testing - type alias') -----
  isTypeAliasForPointer
 
+ ^ referentClass notNil
+ and: [referentClass isTypeAlias
+ and: [referentClass originalType isPointerType]]!
- ^ self headerWord allMask: ExternalType pointerAliasSpec!

Item was changed:
  Object subclass: #FFIPlatformDescription
  instanceVariableNames: 'name osVersion subtype wordSize'
  classVariableNames: 'LastPlatform'
  poolDictionaries: ''
+ category: 'FFI-Kernel-Support'!
- category: 'FFI-Kernel'!
 
  !FFIPlatformDescription commentStamp: 'mt 6/2/2020 15:18' prior: 0!
  This class stores the information about the current (host) platform. It supports testing instances for platform compatibility and specificity. The entire FFI machinery should go through here, when making platform-specific decisions such as when figuring out the #wordSize for pointers to external memory (i.e., ExternalAddress class >> #new) or when looking up compatible definitions for external pools (i.e., ExternalPool class >> #compatibleResolvedDefinitions).
 
 
  1. DETECT PLATFORM CHANGE ON STARTUP
 
  This class is registered for system startup. It then checks whether the current platform is different from the last one. In that case, a selection of FFI classes gets notified such as ExternalObject and ExternalType.
 
 
  2. PLATFORM SPECIFICITY
 
  Platform descriptions may be unspecific, that is, some of their values may be undefined. For example, (FFIPlatformDescription name: 'unix') creates a valid description but is not specific about #osVersion or #wordSize. When comparing such descriptions, precedence of the platform values are:
 
  platform name > osVersion > subtype > wordSize
 
  So, if one description has a #name and the other does not, the first one is more specific. If both have #name but only the second one has #osVersion, the second one is more specific. If one has only #wordSize and another one has only #subtype, the second one is more specific because #subtype has a higher precedence than #wordSize.
 
 
  3. PLATFORM COMPATIBILITY
 
  Platform descriptions implement a notion of compatibility, which is coupled to its notion of specificity as mentioned before. Using the same rules of precedence, compatibility is checked by comparing the description's values. If not specificed, compatibility is assumed. If specified, values must match via #= to be regarded compatible.
 
  Here is an interesting edge case of two compatible platform descriptions:
 
  | p1 p2 |
  p1 := FFIPlatformDescription name: 'Win32' osVersion: '' subtype: 'IX86' wordSize: nil.
  p2 := FFIPlatformDescription name: '' osVersion: 'linux-gnu' subtype: '' wordSize: 8.
  p1 isCompatibleWith: p2.
 
  Consequently, the developer has to be careful with unspecific platform descriptions, which are used, for example, in the definitions of external pools.
 
 
  4. FURTHER READING
 
  - all references to FFIPlatformDescription
  - all senders of #wordSize
  - class comments of ExternalAddress, ExternalType, ExternalPool, ExternalObject
  !

Item was changed:
  (PackageInfo named: 'FFI-Kernel') postscript: 'Smalltalk removeFromStartUpList: ExternalAddress.
  Smalltalk removeFromStartUpList: ExternalObject.
 
+ ExternalType resetAllTypes..
- ExternalType resetAllTypes.
 
  "Re-generate all field accessors because in ExternalData, #size: was replaced with #setSet: and a new constructors for content and container types."
  ExternalStructure defineAllFields.
  '!