[Pkg] FFI: FFI-Callbacks-mt.4.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Apr 30 14:06:13 UTC 2021


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

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

Name: FFI-Callbacks-mt.4
Author: mt
Time: 30 April 2021, 4:06:12.828442 pm
UUID: 549fb596-a536-c944-a48c-646844ddd6ac
Ancestors: FFI-Callbacks-mt.3

Continues work on callback evaluation:
- Lets ABI be a symbol, not a string.
- Adds pool for callback constants.
- Adds stub for ARM64 ABI
- Adds more docs in #primTrunkEntryAddress
- Minor change in callback setup
- Clarify argument types and result types
- Adds stubs for word64 and struct results
- Adds #endianness message to platform description

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

Item was changed:
  ExternalObject subclass: #FFICallback
+ 	instanceVariableNames: 'abi type evaluableObject thunk argumentTypes resultType'
- 	instanceVariableNames: 'abi type evaluableObject thunk argTypes'
  	classVariableNames: 'ThunkToCallbackMap'
  	poolDictionaries: ''
  	category: 'FFI-Callbacks'!

Item was removed:
- ----- Method: FFICallback class>>maxThunkSize (in category 'constants') -----
- maxThunkSize
- 	"see FFICallbackThunk initialize & initializeStdcall:; must be big enough for the largest thunk created"
- 	^ 40!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic: (in category 'callback - evaluators') -----
  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."
  		
  	| offset args |
  	offset := 1.	
+ 	args := Array new: argumentTypes size.
- 	args := Array new: argTypes size - 1. "Skip return type"
  	
  	1 to: args size do: [:argIndex |
  		| argType data |
+ 		argType := argumentTypes at: argIndex.
- 		argType := argTypes at: argIndex + 1. "Skip return type"
  		
  		argType isPointerType
  			ifTrue: [	
  				data := (type handle: handle at: offset).
  				
  				argType referentClass "pointer to atomic"
  					ifNil: [data := data asType: argType]
  					ifNotNil: [:structClass | "pointer to external structure or union"
  						argType isTypeAliasToPointer
  							ifTrue: [data := structClass fromHandle: data getHandle asByteArrayPointer]
  							ifFalse: [data := structClass fromHandle: data getHandle]] ]
  			ifFalse: [ "non-pointer type"
  				self flag: #floats. "mt: When should we switch to callbackContext floatRegArgs?"
  				data := argType handle: handle at: offset.
  
  				argType isAtomic
  					ifFalse: ["structure type, most likely type alias to pointer"
  						data := argType referentClass
  							fromHandle: (ExternalAddress fromInteger: data) asByteArrayPointer]
  					ifTrue: [ argType isTypeAlias
  						ifTrue: [ "alias to atomic type"
  							data := argType referentClass fromHandle: data]
  						ifFalse: [ "atomic, non-pointer type"
  							data := data ";-)"]] ].
  
  		args at: argIndex put: data.
  		offset := offset + ((type byteSize max: argType byteSize) roundUpTo: type byteSize)].
  	
  	^ self
  		setResult: (evaluableObject valueWithArguments: args)
  		inContext: callbackContext.!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic_ARM32: (in category 'callback - evaluators') -----
  evaluateDynamic_ARM32: callbackContext
  	"Set handle to access arguments as most appropriate for the ABI. For ''RISCs'' it is the pointer to the integer register."
+ 	<abi: #ARM32> <evaluator>
- 	<abi: 'ARM32'> <evaluator>
  	
  	self setArgData: callbackContext intRegArgs.
  	^ self evaluateDynamic: callbackContext!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic_IA32: (in category 'callback - evaluators') -----
  evaluateDynamic_IA32: callbackContext
  	"Set handle to access arguments as most appropriate for the ABI. For x86 (i.e. IA32) it is the stack pointer."
+ 	<abi: #IA32> <evaluator>
- 	<abi: 'IA32'> <evaluator>
  	
+ 	| stackPtr offset args |
+ 	stackPtr := callbackContext stackPtr. "For IA32, all arguments are on the stack." 
+ 
+ 	handle := stackPtr getHandle.
+ 	type := stackPtr contentType. "intptr_t"
+ 
+ 	offset := 1.	
+ 	args := Array new: argumentTypes size.
+ 	
+ 	1 to: args size do: [:argIndex |
+ 		| argType data |
+ 		argType := argumentTypes at: argIndex.
+ 		data := argType handle: handle at: offset.
+ 		args at: argIndex put: data.
+ 		
+ 		"Move the offset. Consider the byte-alignment?"
+ 		offset := offset + ((type byteSize max: argType byteSize) roundUpTo: type byteSize)].
+ 	
+ 	^ self
+ 		setResult: (evaluableObject valueWithArguments: args)
+ 		inContext: callbackContext!
- 	self setArgData: callbackContext stackPtr.
- 	^ self evaluateDynamic: callbackContext!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic_X64: (in category 'callback - evaluators') -----
  evaluateDynamic_X64: callbackContext
  	"Set handle to access arguments as most appropriate for the ABI. For ''RISCs'' it is the pointer to the integer register."
+ 	<abi: #X64> <evaluator>
- 	<abi: 'X64'> <evaluator>
  	
  	self setArgData: callbackContext intRegArgs.
  	^ self evaluateDynamic: callbackContext!

Item was changed:
  ----- Method: FFICallback>>evaluateDynamic_X64Win64: (in category 'callback - evaluators') -----
  evaluateDynamic_X64Win64: callbackContext
  	"Set handle to access arguments as most appropriate for the ABI. For ''RISCs'' it is the pointer to the integer register."
+ 	<abi: #X64Win64> <evaluator>
- 	<abi: 'X64Win64'> <evaluator>
  	
  	self setArgData: callbackContext intRegArgs.
  	^ self evaluateDynamic: callbackContext!

Item was changed:
  ----- Method: FFICallback>>init__ccall_ARM32 (in category 'initialization - thunk prepare') -----
  init__ccall_ARM32
+ 	<abi: #ARM32> <init>
- 	<abi: 'ARM32'> <init>
  	"Initialize the receiver with a __ccall thunk.  The thunk calls thunkEntry in the IA32ABI plugin,
  	 whose source is in platforms/Cross/plugins/IA32ABI/arm32abicc.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 r0, long r1, long r2, long r3,
  		            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:."
  
  	"0x0 <thunk+0>:		mov     r12, sp			; 0xe1a0c00d
   	 0x4 <thunk+4>:		sub     sp, sp, #16		; 0xe24dd010
   	 0x8 <thunk+8>:		str     pc, [sp, #0]		; 0xe58df000 N.B. passes thunk+16; thunkEntry compensates
   	 0xc <thunk+12>:		str     r12, [sp,#4]		; 0xe58dc004
   	 0x10 <thunk+16>:	str     lr, [sp, #12]		; 0xe58de00c
   	 0x14 <thunk+20>:	ldr     r12, [pc, #8]		; 0xe59fc008
   	 0x18 <thunk+24>:	blx     r12				; 0xe12fff3c
   	 0x1c <thunk+28>:	add     sp, sp, #12		; 0xe28dd00c
   	 0x20 <thunk+32>:	ldr     pc, [sp], #4!!		; 0xe49df004 ; pop     {pc}
   	 0x24 <thunk+36>:     .word thunkEntry"
  	self flag: #hidden. "mt: How is the thunk's handle stored to lookup this instance upon callback later?"
  	thunk getHandle
  		unsignedLongAt:   1 put: 16re1a0c00d;
  		unsignedLongAt:   5 put: 16re24dd010;
  		unsignedLongAt:   9 put: 16re58df000;
  		unsignedLongAt: 13 put: 16re58dc004;
  		unsignedLongAt: 17 put: 16re58de00c;
  		unsignedLongAt: 21 put: 16re59fc008;
  		unsignedLongAt: 25 put: 16re12fff3c;
  		unsignedLongAt: 29 put: 16re28dd00c;
  		unsignedLongAt: 33 put: 16re49df004;
  		shortPointerAt: 37 put: self thunkEntryAddress.!

Item was added:
+ ----- Method: FFICallback>>init__ccall_ARM64 (in category 'initialization - thunk prepare') -----
+ init__ccall_ARM64
+ 	<abi: #ARM64> <init>
+ 	"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:."
+ 
+ 	self shouldBeImplemented
+ 
+ 	"self newCCall"!

Item was changed:
  ----- Method: FFICallback>>init__ccall_IA32 (in category 'initialization - thunk prepare') -----
  init__ccall_IA32
+ 	<abi: #IA32> <init>
- 	<abi: 'IA32'> <init>
  	"Initialize the receiver with a __ccall thunk.  The thunk calls thunkEntry in the IA32ABI plugin,
  	 whose source is in platforms/Cross/plugins/IA32ABI/x64win64abicc.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
  		thunkEntry(void *thunkp, sqIntptr_t *stackp)
  
  	thunkEntry then collects the various arguments (thunk, stack pointer) in a VMCallbackContext and
  	invokes the callback via invokeCallbackContext:."
  
  	"thunk:		push   %esp				0x54							0xa1905454
  	 thunk+01:	push   %esp				0x54
  	 thunk+02:	nop   						0x90
  	 thunk+03:	mov    $thunkEntry,%eax	0xb8 0x00 0x00 0x00 0x00	0x00000000 - entry
  	 thunk+08:	nop   						0x90							0x68909090
  	 thunk+09:	nop   						0x90
  	 thunk+10:	nop   						0x90
  	 thunk+11:	push   $thunk				0x68 0x00 0x00 0x00 0x00	0x00000000 - thunk
  	 thunk+16:	call   *%eax					0xff 0xd0						0xc483d0ff
  	 thunk+18:	add    $0xC,%esp			0x83 0xc4 0x0C				0x9090c30C
  	 thunk+21:	ret							0xc3
  	 thunk+22:	nop							0x90
  	 thunk+23:	nop							0x90"
  	thunk getHandle
  		unsignedLongAt:  1 put: 16rB8905454;
  		shortPointerAt: 5 put: self thunkEntryAddress;
  		unsignedLongAt:  9 put: 16r68909090;
  		shortPointerAt: 13 put: thunk getHandle;
  		unsignedLongAt: 17 put: 16rC483D0FF;
  		unsignedLongAt: 21 put: 16r9090C30C!

Item was changed:
  ----- Method: FFICallback>>init__ccall_X64 (in category 'initialization - thunk prepare') -----
  init__ccall_X64
+ 	<abi: #X64> <init>
- 	<abi: 'X64'> <init>
  	"Initialize the receiver with a __ccall thunk.  The thunk calls thunkEntry in the IA32ABI plugin,
  	 whose source is in platforms/Cross/plugins/IA32ABI/x64sysvabicc.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
  		thunkEntry(long a0, long a1, long a2, long a3, long a4, long a5,
  		            double d0, double d1, double d2, double d3,
  		            double d4, double d5, double d6, double d7,
  		            void *thunkp, 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:."
  
  	"thunk+0x0:	pushq  %rsp							54
  	 thunk+0x1:	pushq  %rsp							54
  	 thunk+0x4:	movabsq $thunk, %rax					48 b8 b0..b7 eight bytes of thunk address a.k.a. handle
  	 thunk+0xc:	pushq  %rax							50
  	 thunk+0xd:	movabsq $thunkEntry, %rax			48 b8 b0..b7 eight bytes of the thunkEntry address
  	 thunk+0x17:	callq  *%rax							ff d0
  	 thunk+0x19:	addq   $0x18, %rsp					48 83 c4 18
  	 thunk+0x1d:	retq									c3
  	 thunk+0x1e:	nop										90
  	 thunk+0x1f:	nop										90"
  	thunk getHandle
  		unsignedLongAt:		  1 put: 16rb8485454;
  		longPointerAt:			  5 put: thunk getHandle;
  		unsignedLongAt:		13 put: 16r00b84850; "00 is the first byte of the 64-bit constant the movabsq/0x48 opcode moves"
  		longPointerAt:			16 put: self thunkEntryAddress;
  		unsignedByteAt:		24 put: 16rff;
  		unsignedLongAt:		25 put: 16rc48348d0;
  		unsignedLongAt:		29 put: 16r9090c318.!

Item was changed:
  ----- Method: FFICallback>>init__ccall_X64Win64 (in category 'initialization - thunk prepare') -----
  init__ccall_X64Win64
+ 	<abi: #X64Win64> <init>
- 	<abi: 'X64Win64'> <init>
  	"Initialize the receiver with a __ccall thunk.  The thunk calls thunkEntry in the IA32ABI plugin,
  	 whose source is in platforms/Cross/plugins/IA32ABI/x64win64abicc.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 long rcx, long long rdx,
  		      		long long r8, long long r9,
  					void *thunkp, sqIntptr_t *stackp)
  
  	thunkEntry then collects the various arguments (thunk, integer register arguments, stack pointer)
  	in a VMCallbackContext and invokes the callback via invokeCallbackContext:."
  
  	"thunk+0x0:	pushq  %rsp							54
  	 thunk+0x1:	pushq  %rsp							54
  	 thunk+0x4:	movabsq $thunk, %rax					48 b8 b0..b7 eight bytes of thunk address a.k.a. addressField
  	 thunk+0xc:	pushq  %rax							50
  	 thunk+0xd:	subq   $0x20, %rsp						48 83 c4 e0 (this is addq -20 since the immediate is signed extended)
  	 thunk+0x11:	movabsq $thunkEntry, %rax			48 b8 b0..b7 eight bytes of the thunkEntry address
  	 thunk+0x1b:	callq  *%rax							ff d0
  	 thunk+0x1d:	addq   $0x38, %rsp					48 83 c4 38
  	 thunk+0x21:	retq									c3
  	 thunk+0x22:	nop										90
  	 thunk+0x23:	nop										90"
  	thunk getHandle
  		unsignedLongAt:		  1 put: 16rb8485454;
  		longPointerAt: 			  5 put: thunk getHandle;
  		unsignedLongAt:		13 put: 16rc4834850; 
  		unsignedLongAt:		17 put: 16r00b848e0; "00 is the first byte of the 64-bit constant the movabsq/0x48 opcode moves"
  		longPointerAt:			20 put: self thunkEntryAddress;
  		unsignedByteAt:		28 put: 16rff;
  		unsignedLongAt:		29 put: 16rc48348d0;
  		unsignedLongAt:		33 put: 16r9090c338.!

Item was changed:
  ----- Method: FFICallback>>init__stdcall_IA32: (in category 'initialization - thunk prepare') -----
  init__stdcall_IA32: numBytes
+ 	<abi: #IA32> <init>
- 	<abi: 'IA32'> <init>
  	"Initialize the receiver with a __stdcall thunk with numBytes argument bytes. (See #init__ccall_IA32 for more info)"
  	"thunk:		push   %esp				0x54							0xa1905454
  	 thunk+01:	push   %esp				0x54
  	 thunk+02:	nop   						0x90
  	 thunk+03:	mov    $thunkEntry,%eax	0xb8 0x00 0x00 0x00 0x00	0x00000000 - entry
  	 thunk+08:	nop   						0x90							0x68909090
  	 thunk+09:	nop   						0x90
  	 thunk+10:	nop   						0x90
  	 thunk+11:	push   $thunk				0x68 0x00 0x00 0x00 0x00	0x00000000 - thunk
  	 thunk+16:	call   *%eax					0xff 0xd0						0xc483d0ff
  	 thunk+18:	add    $0xC,%esp			0x83 0xc4 0x0C				0xBYTSc20C
  	 thunk+21:	ret    $bytes				0xc2 0xBY 0xTS"
  
  	thunk getHandle
  		unsignedLongAt:  1 put: 16rB8905454;
  		shortPointerAt: 5 put: self thunkEntryAddress;
  		unsignedLongAt:  9 put: 16r68909090;
  		shortPointerAt: 13 put: thunk getHandle;
  		unsignedLongAt:  17 put: 16rC483D0FF;
  		unsignedShortAt: 21 put: 16rC20C;
  		unsignedShortAt: 23 put: numBytes.!

Item was changed:
  ----- Method: FFICallback>>primThunkEntryAddress (in category 'initialization - thunk prepare') -----
  primThunkEntryAddress "^<Integer>"
  	"Answer the address of the entry-point for thunk callbacks:
+ 		IA32: long
+ 			thunkEntry(void *thunkp, long *stackp);
+ 		X64: long
+ 			thunkEntry(long a0, long a1, long a2, long a3, long a4, long a5,
+ 							double d0, double d1, double d2, double d3,
+ 							double d4, double d5, double d6, double d7,
+ 							void *thunkp, sqIntptr_t *stackp);
+ 		X64Win64 long long
+ 			thunkEntry(long long rcx, long long rdx,
+ 							long long r8, long long r9,
+ 							void *thunkp, sqIntptr_t *stackp);
+ 		ARM32: long long
+ 			thunkEntry(long r0, long r1, long r2, long r3,
+ 							double d0, double d1, double d2, double d3,
+ 							double d4, double d5, double d6, double d7,
+ 							void *thunkpPlus16, sqIntptr_t *stackp);
+ 		ARM64: 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);
- 		x86: long thunkEntry(void *thunkp, long *stackp);
- 		x64: long thunkEntry(long a, long b, long c, long d, long, e, long f,
- 								double d0, double d1, double d2, double d3,
- 								double d4, double d5, double d6, double d7,
- 								void *thunkp, long *stackp);
- 		ARM: long thunkEntry(long a, long b, long c, long d,
- 								double d0, double d1, double d2, double d3,
- 								double d4, double d5, double d6, double d7,
- 								void *thunkp, long *stackp);
  	 etc.
  	 This is the function a callback thunk/trampoline should call to initiate a callback."
  	<primitive: 'primThunkEntryAddress' module: 'IA32ABI' error: errorCode>
  	^self primitiveFailed!

Item was removed:
- ----- Method: FFICallback>>setArgTypes:evaluableObject: (in category 'initialization') -----
- setArgTypes: externalTypes evaluableObject: blockOrMessage
- 
- 	
- 	abi := FFIPlatformDescription current abi.
- 	handle := nil.
- 	type := nil.
- 	
- 	evaluableObject := blockOrMessage.
- 	argTypes := externalTypes.
- 
- 
- 
- 
- 
- 	"Support for callee pop callbacks (Pascal calling convention such as the Win32 stdcall: convention) are supported using the <calleepops: N> pragma which specifies how many bytes to pop. See http://forum.world.st/Pharo-FFI-on-aarch64-arm64-td5096777.html#a5096786."
- 	thunk := FFICallbackMemory allocateExecutableBlock.
- 	self init__ccall.
- 	"self init__stdcall: 0."
- 	"(method pragmaAt: #calleepops:)
- 		ifNil: [self init__ccall]
- 		ifNotNil: [:pragma | self init__stdcall: (pragma argumentAt: 1)]."
- 		
- 	"numEvaluatorArgs := (evaluator := method selector) numArgs.
- 	self addToThunkTable"
- 	ThunkToCallbackMap at: thunk getHandle put: self!

Item was changed:
  ----- Method: FFICallback>>setBlock:signature: (in category 'initialization') -----
  setBlock: aBlock "<BlockClosure>" signature: signature "<String>"
  
  	self
+ 		setTypes: (ExternalType lookupTypes: signature)
- 		setArgTypes: (ExternalType lookupTypes: signature)
  		evaluableObject: aBlock.!

Item was changed:
  ----- Method: FFICallback>>setMessage: (in category 'initialization') -----
  setMessage: aMessageSend
  	"Fetch the argTypes from <callback: ...> pragma in method."
  	
  	| method |
  	self assert: [aMessageSend receiver notNil].
  	
  	method := aMessageSend receiver class lookupSelector: aMessageSend selector.
  	
  	self
+ 		setTypes: ((method pragmaAt: #callback:) argumentAt: 1)
- 		setArgTypes: ((method pragmaAt: #callback:) argumentAt: 1)
  		evaluableObject: aMessageSend.!

Item was changed:
  ----- Method: FFICallback>>setMessage:signature: (in category 'initialization') -----
  setMessage: aMessageSend signature: signature
  	"Override the argTypes from <callback: ...> pragma in method."
  	
  	self assert: [aMessageSend receiver notNil].
  	
  	self
+ 		setTypes: (ExternalType lookupTypes: signature)
- 		setArgTypes: (ExternalType lookupTypes: signature)
  		evaluableObject: aMessageSend.!

Item was changed:
  ----- Method: FFICallback>>setResult:inContext: (in category 'callback') -----
  setResult: anObject inContext: aCallbackContext
  	"Set the result in the callback context. Add some fast checks to detect errors."
  	
+ 	resultType isPointerType
+ 		ifTrue: [			
+ 			"an ExternalStructure, an ExternalUnion, an ExternalData, ..."
+ 			^ aCallbackContext externalObjectResult: anObject].
+ 		
+ 	resultType atomicType = 0 "void"
+ 		ifTrue: ["Quick exit for void return type."
- 	argTypes first atomicType = 0 "void"
- 		ifTrue: [
- 			"Quick exit for void return type."
  			^ aCallbackContext voidResult].
  
  	anObject isInteger
  		ifTrue: [
+ 			self assert: [resultType isIntegerType].
+ 			self flag: #todo. "mt: ABI #X64Win64 has special treatment for word64, too. But maybe it is not needed."
+ 			^ (anObject isLarge and: [FFIPlatformDescription current abi = #IA32])
+ 				ifTrue: [aCallbackContext word64Result: anObject]
+ 				ifFalse: [aCallbackContext wordResult: anObject]].
- 			self assert: [argTypes first isIntegerType].
- 			^ aCallbackContext wordResult: anObject].
  
  	anObject isBoolean
  		ifTrue: [
+ 			self assert: [resultType atomicType = 1 "bool"].
- 			self assert: [argTypes first atomicType = 1 "bool"].
  			^ aCallbackContext wordResult: anObject].		
  
  	anObject isFloat
  		ifTrue: [
+ 			self assert: [resultType atomicType >= 12 "float/double"].			
- 			self assert: [argTypes first atomicType >= 12 "float/double"].			
  			^ aCallbackContext floatResult: anObject].
  
+ 	self notify: 'Unkown result type.'.
+ 	^ aCallbackContext errorResult!
- 	"Try to push pointer for external object."
- 	^ aCallbackContext externalObjectResult: anObject!

Item was added:
+ ----- Method: FFICallback>>setResultType:argumentTypes:evaluableObject: (in category 'initialization') -----
+ setResultType: anExternalType argumentTypes: moreExternalTypes evaluableObject: blockOrMessage
+ 
+ 	
+ 	abi := FFIPlatformDescription current abi.
+ 	handle := nil.
+ 	type := nil.
+ 	
+ 	evaluableObject := blockOrMessage.
+ 	argumentTypes := moreExternalTypes.
+ 	resultType := anExternalType.
+ 
+ 
+ 
+ 
+ 	"Support for callee pop callbacks (Pascal calling convention such as the Win32 stdcall: convention) are supported using the <calleepops: N> pragma which specifies how many bytes to pop. See http://forum.world.st/Pharo-FFI-on-aarch64-arm64-td5096777.html#a5096786."
+ 	thunk := FFICallbackMemory allocateExecutableBlock.
+ 	self init__ccall.
+ 	"self init__stdcall: 0."
+ 	"(method pragmaAt: #calleepops:)
+ 		ifNil: [self init__ccall]
+ 		ifNotNil: [:pragma | self init__stdcall: (pragma argumentAt: 1)]."
+ 		
+ 	"numEvaluatorArgs := (evaluator := method selector) numArgs.
+ 	self addToThunkTable"
+ 	ThunkToCallbackMap at: thunk getHandle put: self!

Item was added:
+ ----- Method: FFICallback>>setTypes:evaluableObject: (in category 'initialization') -----
+ setTypes: externalTypes evaluableObject: blockOrMessage
+ 
+ 	self
+ 		setResultType: externalTypes first
+ 		argumentTypes: externalTypes allButFirst
+ 		evaluableObject: blockOrMessage.!

Item was added:
+ SharedPool subclass: #FFICallbackConstants
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'MaxThunkSize ResultTypeDouble ResultTypeStruct ResultTypeWord ResultTypeWord64'
+ 	poolDictionaries: ''
+ 	category: 'FFI-Callbacks'!

Item was added:
+ ----- Method: FFICallbackConstants class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"
+ 	self initialize.
+ 	"
+ 
+ 	"Callback return types. See vmCallback.h"
+ 	ResultTypeWord := 1.
+ 	ResultTypeWord64 := 2.
+ 	ResultTypeDouble := 3.
+ 	ResultTypeStruct := 4.
+ 	
+ 	"See FFICallbackThunk initialize & initializeStdcall:; must be big enough for the largest thunk created"
+ 	MaxThunkSize := 40.!

Item was changed:
  ExternalStructure subclass: #FFICallbackContext
  	instanceVariableNames: ''
  	classVariableNames: ''
+ 	poolDictionaries: 'FFICallbackConstants'
- 	poolDictionaries: ''
  	category: 'FFI-Callbacks'!
+ 
+ !FFICallbackContext commentStamp: 'mt 4/30/2021 11:32' prior: 0!
+ A callback context is a data structure prepared from the VM for accessing the callback's arguments. See FFICallback >> #thunkEntryAddress.
+ 
+ !!!!!! BE AWARE that the actual location of argument values in this structure depend on the current ABI (i.e. 'Application Binary Interface'). See FFIPlatformDescription to access the current ABI.!

Item was changed:
+ ----- Method: FFICallbackContext>>errorResult (in category 'callback result - convenience') -----
- ----- Method: FFICallbackContext>>errorResult (in category 'callback result') -----
  errorResult
  
  	^ self wordResult: -1!

Item was changed:
+ ----- Method: FFICallbackContext>>externalObjectResult: (in category 'callback result - convenience') -----
- ----- Method: FFICallbackContext>>externalObjectResult: (in category 'callback result') -----
  externalObjectResult: anExternalObject
  	"ExternalStructure, ExternalUnion, ExternalData ... handle MUST BE an ExternalAddress"
  	
  	^ self pointerResult: anExternalObject getHandle!

Item was changed:
  ----- Method: FFICallbackContext>>floatResult: (in category 'callback result') -----
  floatResult: aFloat
  
+ 	self flag: #floatVsDouble. "mt: What about result types that expect single-precision floats?"
  	self rvs floatResult: aFloat.
+ 	^ ResultTypeDouble!
- 	^ 3!

Item was changed:
+ ----- Method: FFICallbackContext>>pointerResult: (in category 'callback result - convenience') -----
- ----- Method: FFICallbackContext>>pointerResult: (in category 'callback result') -----
  pointerResult: anExternalAddress
  
  	^ self wordResult: anExternalAddress asInteger!

Item was added:
+ ----- Method: FFICallbackContext>>structResult: (in category 'callback result') -----
+ structResult: anObject
+ 
+ 	self shouldBeImplemented.
+ 	^ ResultTypeStruct!

Item was changed:
+ ----- Method: FFICallbackContext>>voidResult (in category 'callback result - convenience') -----
- ----- Method: FFICallbackContext>>voidResult (in category 'callback result') -----
  voidResult
  
  	self flag: #discuss. "mt: Is this the expected answer in the IA32ABI plugin?"
  	^ self wordResult: 0!

Item was added:
+ ----- Method: FFICallbackContext>>word64Result: (in category 'callback result') -----
+ word64Result: anInteger
+ 	"Separate the integer into high-and-low (big endian) or low-and-high (little endian)."
+ 
+ 	self shouldBeImplemented. "mt: See platforms\Cross\plugins\IA32ABI"
+ 	
+ 	self assert: [anInteger isLarge].
+ 	self assert: [FFIPlatformDescription current wordSize = 4
+ 		or: [FFIPlatformDescription current abi = 'X64Win64']].
+ 
+ 	FFIPlatformDescription current endianness caseOf: {
+ 		[ #little ] -> [].
+ 		[ #big ] -> [].
+ 	}.
+ 	
+ 	
+ 	^ ResultTypeWord64!

Item was changed:
  ----- Method: FFICallbackContext>>wordResult: (in category 'callback result') -----
  wordResult: aValue
- 	"Accept any value in the -2^31 to 2^32-1 range or booleans."
  
  	aValue isBoolean ifTrue:
  		[self rvs booleanResult: aValue].
  	
  	aValue isInteger ifTrue:
  		[aValue >= 0
  			ifTrue: [self rvs positiveIntegerResult: aValue]
  			ifFalse: [self rvs integerResult: aValue]].
  
+ 	^ ResultTypeWord!
- 	^1!

Item was changed:
  ByteArray variableByteSubclass: #FFICallbackMemory
  	instanceVariableNames: ''
  	classVariableNames: 'AccessProtect AllocatedThunks ExecutablePages LifoCallbackSemaphore'
+ 	poolDictionaries: 'FFICallbackConstants'
- 	poolDictionaries: ''
  	category: 'FFI-Callbacks'!
  
  !FFICallbackMemory commentStamp: 'mt 6/17/2020 12:24' prior: 0!
  Interface for memory allocation using the IA32ABI plugin. Also used as a compatibility layer for Alien.
  
  ***
  
  An instance of FFICallbackThunk is a reference to a machine-code thunk/trampoline that calls-back into the VM.  The reference can be passed to C code which can use it as a function pointer through which to call-back into Smalltalk.  The machine-code thunk/trampoline is different for each instance, hence its address is a unique key that can be used to assocuate the Smalltalk side of the call-back (e.g. a block) with the thunk.  Since thunks must be executable and some OSs may not provide default execute permission on memory returned by malloc we may not be able to use malloc directly.  Instead we rely on a primitive to provide memory that is guaranteed to be executable.  ExternalAddress class>>allocateExecutablePage answers an instance of ExternalData that references an executable piece of memory that is some (possiby unitary) multiple of the pagesize.  Class-side code then parcels out pieces of a page to individual thunks.  These pieces are recycled when thunks are reclaimed.  Sinc
 e the first byte of a thunk is non-zero we can use it as a flag indicating if the piece is in use or not.
  
  See FFICallback for the higher-level construct that represents a Smalltalk block to be run in response to a callback.  Callbacks wrap instances of FFICallbackThunk and FFICallbackContext instances that describe the stack layout and register contents for receiving callback arguments.
  
  Class Variables
  AccessProtect <Semaphore> critical section for ExecutablePages (de)allocation
  AllocatedThunks <AlienWeakTable of <FFICallbackThunk -> Integer>> - weak collection of thunks, used to return thunk storage to the executable page pool.
  ExecutablePages <Set of: Alien "executable page"> - collection of pages with execute permissions used to provide executable thunks!

Item was changed:
  ----- Method: FFICallbackMemory class>>allocateExecutableBlock (in category 'executable pages') -----
  allocateExecutableBlock
  
  	| blockSize |
+ 	blockSize := MaxThunkSize.
- 	blockSize := FFICallback maxThunkSize.
  	AccessProtect critical:
  		[ExecutablePages do:
  			[:page |
  			1 to: page size - blockSize by: blockSize do:
  				[:i|
  				(page at: i) = 0 ifTrue:
  					[page at: i put: 1.
  					 ^ page blockAt: i byteSize: blockSize]]]].
  	AccessProtect critical: [
  		| newPage |
  		newPage := ExecutablePages add: self allocateExecutablePage.
  		^ (newPage blockAt: 1 byteSize: blockSize)
  			at: 1 put: 1;
  			yourself]!

Item was changed:
  ----- Method: FFIPlatformDescription>>abi (in category '*FFI-Callbacks') -----
  abi
  
  	| processor |
  	processor := self subtype asLowercase.
  	
  	(processor = 'arm' or: [(processor beginsWith: 'armv') and: [processor fifth <= $7]])
+ 		ifTrue: [^ #'ARM32'].
- 		ifTrue: [^ 'ARM32'].
  	(processor first = $i and: [processor = 'intel' or: ['i#86' match: processor]])
+ 		ifTrue: [^ #'IA32'].
- 		ifTrue: [^ 'IA32'].
  
  	(processor first = $x and: [processor = 'x64' or: [('x86#64*' match: processor)]])
+ 		ifTrue: [^ self isWindows ifTrue: [#'X64Win64'] ifFalse: [#'X64']].
- 		ifTrue: [^ self isWindows ifTrue: ['X64Win64'] ifFalse: ['X64']].
  		
+ 	^ #'UNKNOWN_ABI'!
- 	^ 'UNKNOWN'!

Item was added:
+ ----- Method: FFIPlatformDescription>>endianness (in category '*FFI-Callbacks') -----
+ endianness
+ 
+ 	^ Smalltalk endianness!



More information about the Packages mailing list