[squeak-dev] FFI: FFI-Callbacks-mt.27.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 12 12:34:42 UTC 2021


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

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

Name: FFI-Callbacks-mt.27
Author: mt
Time: 12 August 2021, 2:34:41.941321 pm
UUID: 3083fa60-01de-fd48-a299-3b344e4e5883
Ancestors: FFI-Callbacks-mt.26

In dynamic callback evaluation, do not unpack pointer arguments anymore, which was wrong for stack args anyway.

=============== Diff against FFI-Callbacks-mt.26 ===============

Item was changed:
  ----- Method: CStandardLibrary>>compare:through: (in category '*FFI-Callbacks') -----
  compare: contentType through: evaluable
+ 	"Answers a callback for comparing the given contentType through the given evaluable, i.e., messages sends or blocks. Supports pointer types as contentType via array-type indirection. Automatically unpacks pointers to atomics so that evaluable can directly work on Smalltalk objects. Does not support void as contentType."
- 	"Answers a callback for comparing the given contentType through the given evaluable, i.e., messages sends or blocks. Supports pointer types as contentType."
  	
  	<callback: int32_t (*)(const void*, const void*)>
  	
  	| argType signature |
  	self assert: [evaluable numArgs = 2].
  	
  	argType := contentType isPointerType
+ 		ifTrue: [(contentType asArrayType: nil) "HACKY!!"]
- 		ifTrue: [(contentType asArrayType: nil)]
  		ifFalse: [contentType].
  
  	signature := ((thisContext method pragmaAt: #callback:) argumentAt: 1) copy.
  	signature at: 2 put: argType asPointerType.
  	signature at: 3 put: argType asPointerType.	
+ 	
+ 	^ ((contentType isAtomic or: [contentType isPointerType])
+ 		ifTrue: [ [:arg1 :arg2 | evaluable value: arg1 value value: arg2 value] ]
+ 		ifFalse: [evaluable]) gcSignature: signature!
- 			 
- 	^ evaluable gcSignature: signature!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic: (in category 'evaluating') -----
  evaluateDynamic: callbackContext
  	"Read all arguments and make the call(back). Assume that 'handle' and 'type' are set correctly. Only watch out for the sign. See field definition in FFICallbackContext to explore alternative ways to read the arguments."
  		
  	| arguments stack stackType stackByteOffset intArgs intPos floatArgs floatPos |
  	
  	stack := callbackContext stackPtr getHandle.
  	stackType := callbackContext stackPtr contentType.
  	stackByteOffset := 1.	
  	
  	intArgs := callbackContext intRegArgs.
  	intPos := 0.
  	floatArgs := callbackContext floatRegArgs.
  	floatPos := 0.
  	
  	arguments := Array new: argumentTypes size.
  	1 to: arguments size do: [:argIndex |
  		| argType data isPointer |
  		argType := argumentTypes at: argIndex.
  
  		"1) Try to read arguments from registers."
  		data := (intPos < intArgs size and: [(isPointer := argType isPointerType) or: [argType isIntegerType]])
  			ifTrue: [intPos := intPos + 1. intArgs at: intPos]
  			ifFalse: [(floatPos < floatArgs size and: [argType isFloatType])
  				ifTrue: [floatPos := floatPos + 1. floatArgs at: floatPos]].
  
  		data
  			ifNotNil: [ "1b) Read pointers from register value."
  				isPointer ifFalse: ["data is already an integer"] ifTrue: [
+ 					data := argType "isPointerType!!" handle: data "address-as-integer" at: 1]]
- 					data := (ExternalData
- 						fromHandle: (ExternalAddress fromInteger: data)
- 						type: argType asNonPointerType "contentType") value]]
  			ifNil: [ "2) If nothing was read, read the argument from the stack."
+ 				data := argType handle: stack at: stackByteOffset.
- 				data := (argType handle: stack at: stackByteOffset) value.
  				stackByteOffset := stackByteOffset
  					+ ((stackType byteSize max: argType byteSize) roundUpTo: stackType byteAlignment)].					
  
  		arguments at: argIndex put: data].
  		
  	^ self
  		setResult: (self evaluableObject valueWithArguments: arguments)
  		inContext: callbackContext!

Item was changed:
  ----- Method: FFICallback>>init__ccall_ARM64 (in category 'private') -----
  init__ccall_ARM64
  	<abi: #ARM64> <init_ccall>
  	"Initialize the receiver with a __ccall thunk.  The thunk calls thunkEntry in the Alien/IA32ABI plugin,
  	 whose source is in platforms/Cross/plugins/IA32ABI/arm64abicc.c.  thunkEntry is the entry point
  	 for Callbacks. The objective of the thunk is to call thunkEntry with all arguments to the call of the
  	 thunk (registers and stack) as well as a pointer to the thunk itself.  thunkEntry is as follows:
  	
  		long long
  		thunkEntry(long x0, long x1, long x2, long x3,
  				       long x4, long x5, long x6, long x7,
  				       double d0, double d1, double d2, double d3,
  				       double d4, double d5, double d6, double d7,
  				       void *thunkpPlus16, sqIntptr_t *stackp)
  
  	thunkEntry then collects the various arguments (thunk, integer register arguments, floating-point
  	register arguments, stack pointer) in a VMCallbackContext and invokes the callback via invokeCallbackContext:."
  
  	| bytes |
  	bytes := #["0		mov	x16, sp"			16rF0 16r03 16r00 16r91
  				"4		sub	sp, sp, #0x20"			16rFF 16r83 16r00 16rD1
  				"8		stp	x16, x30, [sp, #0x8]"	16rF0 16rFB 16r00 16rA9
  				"c		bl		0x10"				16r01 16r00 16r00 16r94
  				"10		str		x30, [sp]"			16rFE 16r03 16r00 16rF9
  				"14		ldr		x16, #0x14"		16rB0 16r00 16r00 16r58
  				"18		blr		x16	"				16r00 16r02 16r3F 16rD6
  				 "1C	ldr		x30, [sp, #0x16]"	16rFE 16r0B 16r40 16rF9
  				 "20	add		sp, sp, #0x20"		16rFF 16r83 16r00 16r91
  				 "24	ret"							16rC0 16r03 16r5F 16rD6
  													0 0 0 0 0 0 0 0] copy.
+ 	bytes type: #pointer at: 41 put: self primThunkEntryAddress.
- 	bytes type: #uint64_t at: 41 put: self primThunkEntryAddress.
  	self class writeExecutableBlockAt: handle "thunk" bytes: bytes.
  	
  	"self newCCall"!

Item was added:
+ ----- Method: Integer>>pointerAt:length: (in category '*FFI-Callbacks') -----
+ pointerAt: byteOffset length: length
+ 	"Interpret the receiver directly as external address. Now, this lifts Integer to the same level as ByteArray and ExternalAddress ... at least when reading pointers. Polymorphism for the win. :-) "
+ 	
+ 	"self assert: [byteOffset = 1]"
+ 	"self assert: [length = ExternalAddress wordSize]"
+ 	^ ExternalAddress fromInteger: self!

Item was added:
+ ----- Method: Integer>>pointerAt:put:length: (in category '*FFI-Callbacks') -----
+ pointerAt: byteOffset put: pointer length: length
+ 	"Interpret the receiver directly as external address."
+ 	
+ 	self shouldNotImplement. "Integers are read-only."!



More information about the Squeak-dev mailing list