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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 20 15:16:21 UTC 2021


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

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

Name: FFI-Kernel-mt.120
Author: mt
Time: 20 April 2021, 5:16:20.338768 pm
UUID: 217ce793-267e-446b-9fea-61066a2b7741
Ancestors: FFI-Kernel-mt.119

ExternalData
- Clarify content-type and container-type (Thanks Nicolas!!! Yet there is still work to be done to support n-ary pointer types)
- Ensure that container-type is always a pointer type
- Remove unnecessary checks in #at:(put:)
- Make #from:to: retain the external address for empty results
- More code clean-up

ByteArray vs. ExternalAddress
- Clarify the role of byte arrays through #isInternalMemory
- Offer an #isNull: check using an external type to better support aliases on pointer-types

ExternalStructure
- Removes (my st00pid) notion of "stable representation" from ExternalStructure
- Updates print-string to surround name with brackets [...] whenever the handle is a ByteArray (i.e. #isInternalMemory) --- and drop all those "*" for external addresses, which is the default, I suppose

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

Item was changed:
+ ----- Method: ByteArray>>isExternalAddress (in category '*FFI-Kernel-testing') -----
- ----- Method: ByteArray>>isExternalAddress (in category '*FFI-Kernel') -----
  isExternalAddress
  	"Return true if the receiver describes the address of an object in the outside world"
  	^false!

Item was added:
+ ----- Method: ByteArray>>isInternalMemory (in category '*FFI-Kernel-testing') -----
+ isInternalMemory
+ 
+ 	^ true!

Item was changed:
+ ----- Method: ByteArray>>isNull (in category '*FFI-Kernel-testing') -----
- ----- Method: ByteArray>>isNull (in category '*FFI-Kernel') -----
  isNull
+ 	"Answer false since only pointers can be null, which is easy for external addresses but unknown for byte arrays without a proper external type for interpretation. See #isTypeAliasForPointer."
+ 	
+ 	^ false!
- 	"Answer false since only external addresses can be null"
- 	^false!

Item was added:
+ ----- Method: ByteArray>>isNull: (in category '*FFI-Kernel-testing') -----
+ isNull: externalType
+ 	"Given the external type, answer whether the receiver holds all null bytes representing a null pointer."
+ 	
+ 	"self assert: [self isInternalMemory]."
+ 	^ externalType isTypeAliasForPointer
+ 		and: [externalType byteSize = self size]
+ 		and: [self allSatisfy: [:byte | byte = 0]]!

Item was added:
+ ----- Method: ExternalAddress>>isInternalMemory (in category 'testing') -----
+ isInternalMemory
+ 
+ 	^ false!

Item was added:
+ ----- Method: ExternalAddress>>isNull: (in category 'testing') -----
+ isNull: externalType
+ 	"Overridden to make use of #isNull. This fails if the provided pointer size does not match, which indicates an inconsistency in the system's type objects for the current platform. See 'housekeeping' protocol in ExternalType."
+ 
+ 	self assert: [externalType pointerSize = self size].
+ 	^ self isNull!

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

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

Item was added:
+ ----- Method: ExternalData>>asString (in category 'converting') -----
+ asString
+ 
+ 	^ size
+ 		ifNil: [self fromCString]
+ 		ifNotNil: [self fromStringBounded]!

Item was changed:
  ----- Method: ExternalData>>assert:at: (in category 'accessing') -----
  assert: expectedType at: index
  
  	self
+ 		assert: [self contentType = expectedType]
+ 		description: 'Wrong content type'.
- 		assert: [type = expectedType asPointerType]
- 		description: 'Wrong type'.
  
  	^ self at: index!

Item was changed:
  ----- Method: ExternalData>>assert:at:put: (in category 'accessing') -----
  assert: expectedType at: index put: value
  
  	self
+ 		assert: [self contentType = expectedType]
+ 		description: 'Wrong content type'.
- 		assert: [type = expectedType]
- 		description: 'Wrong type'.
  
  	^ self at: index put: value!

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].
  
+ 	^ self contentType
- 	^ type asNonPointerType
  		handle: handle
+ 		at: ((index-1) * self contentType 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].
  
+ 	^ self contentType
- 	^ type asNonPointerType
  		handle: handle
+ 		at: ((index-1) * self contentType byteSize) + 1
- 		at: ((index-1) * type asNonPointerType byteSize) + 1
  		put: value!

Item was added:
+ ----- Method: ExternalData>>containerType (in category 'accessing - types') -----
+ containerType
+ 
+ 	^ type!

Item was added:
+ ----- Method: ExternalData>>contentType (in category 'accessing - types') -----
+ contentType
+ 
+ 	self flag: #todo. "mt: For n-ary pointer types, we typically just want to reducy arity by one."
+ 	^ type asNonPointerType!

Item was changed:
+ ----- Method: ExternalData>>externalType (in category 'accessing - types') -----
- ----- Method: ExternalData>>externalType (in category 'accessing') -----
  externalType
  
  	^ type!

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."
- 	"Only copy data if already in object memory, that is, as byte array."
  
+ 	| byteOffset numElements byteSize newType |
- 	| byteOffset numElements byteSize |
- 	lastIndex < firstIndex ifTrue: [
- 		^ (ExternalData fromHandle: #[] type: type)
- 			size: 0; yourself].
- 
  	((1 > firstIndex) or: [size notNil and: [lastIndex > size]])
  		ifTrue: [^ self errorSubscriptBounds: lastIndex].
  
+ 	byteOffset := ((firstIndex-1) * self contentType byteSize)+1.
- 	byteOffset := ((firstIndex-1) * type asNonPointerType byteSize)+1.
  	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"].
- 	byteSize := size * type asNonPointerType byteSize.
  
+ 	^ 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)
+ 							type: newType) size: numElements; yourself]]!
- 	^ handle isExternalAddress
- 		ifTrue: [(ExternalData
- 					fromHandle: handle + byteOffset - 1
- 					type: type) size: numElements; yourself]
- 		ifFalse: [(ExternalData
- 					fromHandle: (handle copyFrom: byteOffset to: byteOffset+byteSize)
- 					type: type) size: numElements; yourself]!

Item was changed:
+ ----- Method: ExternalData>>fromCString (in category 'converting - support') -----
- ----- Method: ExternalData>>fromCString (in category 'converting') -----
  fromCString
  	"Assume that the receiver represents a C string and convert it to a Smalltalk string. hg 2/25/2000 14:18"
  
  	| stream index char |
  	self
+ 		assert: [self containerType = ExternalType string]
+ 		description: 'Wrong content type'.
- 		assert: [self externalType = ExternalType string]
- 		description: 'Wrong type'.
  		
  	stream := WriteStream on: String new.
  	index := 1.
  	[(char := self at: index) = 0 asCharacter] whileFalse: [
  		stream nextPut: char.
  		index := index + 1].
  	^stream contents!

Item was changed:
+ ----- Method: ExternalData>>fromCStrings (in category 'converting - support') -----
- ----- Method: ExternalData>>fromCStrings (in category 'converting') -----
  fromCStrings
  	"Assume that the receiver represents a set of C strings and is teerminated by a empty string and convert it to a Smalltalk ordered collection of strings"
  
  	| stream index char strings str |
  	type isPointerType ifFalse: [self error: 'External object is not a pointer type.'].
+ 	self flag: #bogus. "mt: This format seems to be rather specific to some library. There would normally be pointers to pointers for such a structure. Or does the C standard mention such a format somehow? 'abcd\0efg\0hijklmnopq\0rstuvwxyz\0\0' ??? "
  	strings := OrderedCollection new.
  	index := 1.
  	[
  		stream := WriteStream on: String new.
  		[(char := handle unsignedCharAt: index) = 0 asCharacter]
  			whileFalse: [
  				stream nextPut: char.
  				index := index + 1
  			].
  		str := stream contents.
  		strings addLast: str.
  		str size = 0
  	] whileFalse.
  	^strings!

Item was added:
+ ----- Method: ExternalData>>fromStringBounded (in category 'converting - support') -----
+ fromStringBounded
+ 	"Read byte* as bounded string. You have to set a #size first."
+ 
+ 	| offset step |
+ 	self
+ 		assert: [self contentType = ExternalType byte]
+ 		description: 'Wrong content type'.
+ 
+ 	self sizeCheck.
+ 	
+ 	offset := 1.
+ 	step := self contentType byteSize.
+ 	
+ 	^ String streamContents: [:s |
+ 		size timesRepeat: [
+ 			s nextPut: (handle unsignedCharAt: offset).
+ 			offset := offset + step]]!

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. It does just work once for an external address."
- 	"Reads all bytes into object memory."
  
  	| data |
  	handle isExternalAddress ifFalse: [^ self].
  	self sizeCheck.
  	
+ 	data := ByteArray new: size * self contentType byteSize.
- 	data := ByteArray new: size * type asNonPointerType byteSize.
  	1 to: data size do: [:index |
  		data unsignedByteAt: index put: (handle unsignedByteAt: index)].
  	
  	^ (ExternalData
  		fromHandle: data
+ 		type: self contentType)
- 		type: type asNonPointerType)
  			size: size!

Item was changed:
  ----- Method: ExternalData>>getExternalStructure (in category 'accessing - external structures') -----
  getExternalStructure
  	"Reads an external structure from this external data. If the receiver's handle is an external address, the structure's fields will be copied into object memory. Use #asExternalStructure if you want to avoid this copy."
  	
  	self
+ 		assert: [self contentType referentClass includesBehavior: ExternalStructure]
+ 		description: 'Wrong content type'.
- 		assert: [type referentClass includesBehavior: ExternalStructure]
- 		description: 'Wrong type'.
  
  	^ handle isExternalAddress
+ 		ifTrue: [self getExternalData asExternalStructure]
+ 		ifFalse: [self asExternalStructure]!
- 		ifTrue: [self getExternalData getExternalStructure]
- 		ifFalse: [type referentClass fromHandle: handle]!

Item was changed:
  ----- Method: ExternalData>>getExternalUnion (in category 'accessing - external structures') -----
  getExternalUnion
  	"Reads an external union from this external data. If the receiver's handle is an external address, the union's fields will be copied into object memory. Use #asExternalUnion if you want to avoid this copy."
  
  	self
+ 		assert: [self contentType referentClass includesBehavior: ExternalUnion]
+ 		description: 'Wrong content type'.
- 		assert: [type referentClass includesBehavior: ExternalUnion]
- 		description: 'Wrong type'.
  
  	^ handle isExternalAddress
+ 		ifTrue: [self getExternalData asExternalUnion]
+ 		ifFalse: [self asExternalUnion]!
- 		ifTrue: [self getExternalData getExternalUnion]
- 		ifFalse: [type referentClass fromHandle: handle]!

Item was added:
+ ----- Method: ExternalData>>printContentTypeOn: (in category 'printing') -----
+ printContentTypeOn: stream
+ 
+ 	stream
+ 		nextPut: $<;
+ 		print: self contentType;
+ 		nextPut: $>.!

Item was changed:
  ----- Method: ExternalData>>printOn: (in category 'printing') -----
  printOn: stream
  
  	super printOn: stream.
+ 	self printContentTypeOn: stream.!
- 	self printTypeOn: stream.!

Item was removed:
- ----- Method: ExternalData>>printPointerOn: (in category 'printing') -----
- printPointerOn: stream
- 	"Ignore since it is part of the type, e.g. char* or int[] etc."!

Item was removed:
- ----- Method: ExternalData>>printTypeOn: (in category 'printing') -----
- printTypeOn: stream
- 
- 	stream
- 		nextPut: $<;
- 		print: type;
- 		nextPut: $>.!

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

Item was changed:
  ----- Method: ExternalStructure>>externalType (in category 'accessing') -----
  externalType
  
+ 	^ self class externalType!
- 	| type |
- 	self flag: #ffiDesignSmell. "mt: Note that type aliases to pointer types store pointers via handle as ByteArray, not ExternalAddress."
- 	type := self class externalType.
- 	^ handle class == ExternalAddress
- 		ifTrue: [type asPointerType]
- 		ifFalse: [type]!

Item was removed:
- ----- Method: ExternalStructure>>hasStableRepresentation (in category 'testing') -----
- hasStableRepresentation
- 	"Answers whether the contents of this structure have a stable representation in memory. Basically, every handle that is not a ByteArray can be considered a stable representation. The primary examples would be handles that are 'nil' or an ExternalAddress. Additionally, there can be type aliases to atomic types, which then store the Smalltalk object, e.g. Integer or Float, for such an atomic, e.g. long or float, directly in 'handle'. Those Smalltalk objects are typically immediate (e.g., integers, characters). Note that strings map to char*, which is an (atomic) pointer type and thus accessible only through an ExternalData, which itself always holds an external address as its handle."
- 
- 	^ handle class ~~ ByteArray!

Item was changed:
  ----- Method: ExternalStructure>>isNull (in category 'testing') -----
  isNull
  	
+ 	handle isInternalMemory	
+ 		ifTrue: [^ handle isNull: self externalType].
+ 	handle isExternalAddress
+ 		ifTrue: [^ handle isNull].
+ 	^ handle isNil!
- 	self flag: #ffiDesignSmell. "Type aliases to atomic types store data via handle as Smalltalk object. Consequently, #isNull and #isExternalAddress must not be sent to 'handle' without care. Actually, #isExternalAddress is rather useless at the moment."
- 	
- 	handle class == ExternalAddress ifTrue: [^ handle isNull].
- 	self hasStableRepresentation ifTrue: [^ handle isNil].
- 
- 	self flag: #ffiDesignSmell. "Type aliases to pointer types store pointers via handle as ByteArray, not ExternalAddress (like regular pointer types). Consequently, it is tricky to detect a NULL pointer in the general sense. Here, try to check for #isTypeAliasForPointer and only then check for all bytes being 0 in the byte array."
- 	
- 	"self assert: [self externalType isTypeAliasForPointer => [handle class == ByteArray]]."
- 	^ self externalType isTypeAliasForPointer
- 		and: [handle allSatisfy: [:byte | byte = 0 ]]!

Item was changed:
  ----- Method: ExternalStructure>>printIdentityOn: (in category 'printing') -----
  printIdentityOn: stream
+ 	"Reveal information about this external object's identity so that users can quickly assess the need for inspecting its contents. Users can also infer lifetime properties and consider those when passing this object around in the system."
- 	"Reveal information about this external object's identity so that users can quickly assess the need for inspecting its contents. Users can also infer lifetime properties and consider those when passing this object around in the system. For example, objects that are created on-the-fly when accessing fields via an external address may be of less value compared to objects that are actually hold at those external addresses. See #printPointerOn:."
  
  	handle ifNil: [
  		^ stream nextPutAll: '<UNDEFINED>'].
  
  	self isNull ifTrue: [
+ 		^ stream nextPutAll: '<NULL>'].!
- 		^ stream nextPutAll: '<NULL>'].
- 	
- 	self hasStableRepresentation
- 		ifTrue: ["Object has a stable representation. No need to expose its memory address in the UI."
- 			^ self]
- 		ifFalse: ["Inform the user that this data was copied into object memory."
- 			^ stream nextPut: $<; print: handle identityHash; nextPut: $>].
- !

Item was changed:
  ----- Method: ExternalStructure>>printOn: (in category 'printing') -----
  printOn: stream
  
+ 	handle ifNil: [stream nextPutAll: '? '].
+ 	handle isInternalMemory ifTrue: [stream nextPutAll: '['].
+ 
  	super printOn: stream.
  
+ 	handle ifNil: [stream nextPutAll: ' ?'].
+ 	handle isInternalMemory ifTrue: [stream nextPutAll: ']'].
+ 
- 	self printPointerOn: stream.
  	self printIdentityOn: stream.!

Item was removed:
- ----- Method: ExternalStructure>>printPointerOn: (in category 'printing') -----
- printPointerOn: stream
- 	"Indicate whether this structure points to an external address or whether its contents got copied into a byte array in object memory."
- 
- 	handle ifNil: [^ stream nextPutAll: '<UNDEFINED>'].
- 
- 	handle class == ExternalAddress
- 		ifTrue: [stream nextPutAll: '*'].!

Item was added:
+ ----- Method: ExternalType>>isTypeAlias (in category 'testing') -----
+ isTypeAlias
+ 
+ 	^ false!

Item was added:
+ ----- Method: ExternalType>>isTypeAliasForPointer (in category 'testing') -----
+ isTypeAliasForPointer
+ 
+ 	^ false!

Item was added:
+ ----- Method: Object>>isExternalAddress (in category '*FFI-Kernel') -----
+ isExternalAddress
+ 	"Return true if the receiver describes the address of an object in the outside world. NOTE that this backstop is in Object because atomic types store actual objects (e.g., numbers) as their handle."
+ 
+ 	^ false!

Item was added:
+ ----- Method: Object>>isInternalMemory (in category '*FFI-Kernel') -----
+ isInternalMemory
+ 	"Return true if the receiver describes a region of memory (within Squeak's object memory) to be interpreted (e.g., as external structure, pointer, ...). NOTE that this backstop is in Object because atomic types store actual objects (e.g., numbers) as their handle."
+ 	
+ 	^ false!



More information about the Squeak-dev mailing list