Skip to content
This repository has been archived by the owner on Jan 5, 2023. It is now read-only.

Commit

Permalink
merged changes included in pharo9
Browse files Browse the repository at this point in the history
  • Loading branch information
estebanlm committed Dec 17, 2020
1 parent 8c83425 commit c55234b
Show file tree
Hide file tree
Showing 41 changed files with 146 additions and 77 deletions.
4 changes: 2 additions & 2 deletions src/ThreadedFFI-Tests/TFCallbacksTest.class.st
Expand Up @@ -30,7 +30,7 @@ TFCallbacksTest >> newTestCallbackDoing: aBlock [
runner: runner.
]

{ #category : #tests }
{ #category : #running }
TFCallbacksTest >> setUp [

super setUp.
Expand All @@ -39,7 +39,7 @@ TFCallbacksTest >> setUp [
runner exceptionHandler: TFTestCallbackExceptionHandler new
]

{ #category : #tests }
{ #category : #running }
TFCallbacksTest >> tearDown [

runner exceptionHandler: oldExceptionHandler.
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI-Tests/TFInnerTestStruct.class.st
@@ -1,3 +1,7 @@
"
I am an struct used for testing.
I am the inner struct of a bigger one.
"
Class {
#name : #TFInnerTestStruct,
#superclass : #FFIExternalStructure,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-Tests/TFLongTestStruct.class.st
@@ -1,3 +1,6 @@
"
I am a test structure fill with longs
"
Class {
#name : #TFLongTestStruct,
#superclass : #FFIExternalStructure,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-Tests/TFNestedTestStruct.class.st
@@ -1,3 +1,6 @@
"
I am an struct with another inside.
"
Class {
#name : #TFNestedTestStruct,
#superclass : #FFIExternalStructure,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-Tests/TFPointTestStruct.class.st
@@ -1,3 +1,6 @@
"
I am a point like structure used for test
"
Class {
#name : #TFPointTestStruct,
#superclass : #FFIExternalStructure,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI-Tests/TFTestCallbackExceptionHandler.class.st
@@ -1,3 +1,7 @@
"
I am a test callback exception handler.
I keep the exception so it can be asserted in the test.
"
Class {
#name : #TFTestCallbackExceptionHandler,
#superclass : #Object,
Expand Down
9 changes: 6 additions & 3 deletions src/ThreadedFFI-Tests/TFTestCase.class.st
Expand Up @@ -25,9 +25,12 @@ TFTestCase >> libraryPath [
]

{ #category : #running }
TFTestCase >> runCaseManaged [

super runCase
TFTestCase >> runCaseManaged [

"Skipping in running on an old VM"
TFFIBackend isAvailable ifFalse: [ ^ self skip ].

super runCaseManaged.
]

{ #category : #accessing }
Expand Down
5 changes: 0 additions & 5 deletions src/ThreadedFFI-Tests/TFTestSameThreadRunner.class.st

This file was deleted.

3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/BenchSqueakFFIPlugin.class.st
@@ -1,3 +1,6 @@
"
I am a simple class to benchmark the old squeak FFI implementation
"
Class {
#name : #BenchSqueakFFIPlugin,
#superclass : #Object,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/BenchTFFISameThread.class.st
@@ -1,3 +1,6 @@
"
I am a simple benchmark class to test the TFFISameThread scheme
"
Class {
#name : #BenchTFFISameThread,
#superclass : #Object,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/BenchTFFIWorker.class.st
@@ -1,3 +1,6 @@
"
I am a simple benchmark class to test the TFFIWorker scheme
"
Class {
#name : #BenchTFFIWorker,
#superclass : #BenchTFFISameThread,
Expand Down
@@ -1,3 +1,6 @@
"
I am a test library using the SameThread runner
"
Class {
#name : #TFTestLibraryUsingSameThreadRunner,
#superclass : #FFILibrary,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/TFTestLibraryUsingWorker.class.st
@@ -1,3 +1,6 @@
"
I am a test library using a worker runner
"
Class {
#name : #TFTestLibraryUsingWorker,
#superclass : #TFTestLibraryUsingSameThreadRunner,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/TFUFFIAbstractCallback.class.st
@@ -1,3 +1,6 @@
"
I am an abstract callback using TFFI. Used by tests
"
Class {
#name : #TFUFFIAbstractCallback,
#superclass : #FFICallback,
Expand Down
4 changes: 2 additions & 2 deletions src/ThreadedFFI-UFFI-Tests/TFUFFICallbackTest.class.st
Expand Up @@ -65,10 +65,10 @@ TFUFFICallbackTest >> sumInt:a andInt: b [

{ #category : #running }
TFUFFICallbackTest >> tearDown [

super tearDown.

self ffiLibrary uniqueInstance runner exceptionHandler: oldExceptionHandler.
super tearDown.

]

{ #category : #tests }
Expand Down
@@ -1,3 +1,6 @@
"
I am a failing callback with default value for test usage only
"
Class {
#name : #TFUFFIFailingCallbackWithDefault,
#superclass : #TFUFFIAbstractCallback,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI-Tests/TFUFFIIncrementCallback.class.st
@@ -1,3 +1,6 @@
"
I am a simple callback used by the tests
"
Class {
#name : #TFUFFIIncrementCallback,
#superclass : #TFUFFIAbstractCallback,
Expand Down
11 changes: 7 additions & 4 deletions src/ThreadedFFI-UFFI-Tests/TFUFFITestCase.class.st
Expand Up @@ -31,9 +31,12 @@ TFUFFITestCase >> ffiLibrary: anObject [
]

{ #category : #running }
TFUFFITestCase >> runCaseManaged [

super runCase
TFUFFITestCase >> runCaseManaged [

"Skipping in running on an old VM"
TFFIBackend isAvailable ifFalse: [ ^ self skip ].

super runCaseManaged.
]

{ #category : #running }
Expand All @@ -42,5 +45,5 @@ TFUFFITestCase >> tearDown [
"I have to reset the FFI callout methods to be recompiled using the test runner"
self class withAllSuperclassesDo: [:each | FFIMethodRegistry uniqueInstance resetSingleClass: each].

^ super tearDown
super tearDown
]
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI/TFCalloutAPI.class.st
@@ -1,3 +1,6 @@
"
I am a TFCalloutAPI implementation that overrides the builder to use the one needed to generate TFFI code
"
Class {
#name : #TFCalloutAPI,
#superclass : #FFICalloutAPI,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI-UFFI/TFCalloutMethodBuilder.class.st
@@ -1,3 +1,6 @@
"
I override some methods to correctly generate TFFI methods when using UFFI.
"
Class {
#name : #TFCalloutMethodBuilder,
#superclass : #FFICalloutMethodBuilder,
Expand Down
57 changes: 0 additions & 57 deletions src/ThreadedFFI-UFFI/TFFunctionQueue.class.st

This file was deleted.

4 changes: 4 additions & 0 deletions src/ThreadedFFI/PointerUtils.class.st
@@ -1,3 +1,7 @@
"
I have some primitives used when using objects in FFI calls.
I have them here, because they are really unsafe and never should be called directly.
"
Class {
#name : #PointerUtils,
#superclass : #Object,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFAbstractType.class.st
@@ -1,3 +1,7 @@
"
I am an abstract class with the common behavior of the TFTypes.
A TFType knows how to marshall / unmarshall in a normal call and in a callback.
"
Class {
#name : #TFAbstractType,
#superclass : #FFIExternalReference,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFBooleanType.class.st
@@ -1,3 +1,6 @@
"
I know how to handle the booleans when stored in a int8
"
Class {
#name : #TFBooleanType,
#superclass : #TFDerivedType,
Expand Down
5 changes: 5 additions & 0 deletions src/ThreadedFFI/TFCallback.class.st
@@ -1,3 +1,6 @@
"
I am the Backend implementation of callbacks for UFFI. I use TFFI as a backend
"
Class {
#name : #TFCallback,
#superclass : #FFIExternalReference,
Expand All @@ -17,6 +20,8 @@ Class {
{ #category : #finalization }
TFCallback class >> finalizeResourceData: aCallbackDataHandler [

aCallbackDataHandler isNull ifTrue: [ ^ self ].

self primUnregister: aCallbackDataHandler.
aCallbackDataHandler beNull
]
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFCallbackCannotReturn.class.st
@@ -1,3 +1,6 @@
"
I am an error produced when the callback cannot return correctly.
"
Class {
#name : #TFCallbackCannotReturn,
#superclass : #Error,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFCallbackForkRunStrategy.class.st
@@ -1,3 +1,6 @@
"
I am a simple strategy to run the callbacks in a new process every time.
"
Class {
#name : #TFCallbackForkRunStrategy,
#superclass : #Object,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFCallbackInvocation.class.st
@@ -1,3 +1,7 @@
"
I represent the callback invocation.
I have information about the activation of a given callback.
"
Class {
#name : #TFCallbackInvocation,
#superclass : #FFIExternalObject,
Expand Down
17 changes: 13 additions & 4 deletions src/ThreadedFFI/TFCallbackQueue.class.st
Expand Up @@ -49,6 +49,11 @@ TFCallbackQueue class >> uniqueInstance [
^ UniqueInstance ifNil: [ UniqueInstance := self new ]
]

{ #category : #accessing }
TFCallbackQueue >> callbackProcess [
^ callbackProcess
]

{ #category : #operations }
TFCallbackQueue >> executeCallback: aCallbackInvocation [

Expand Down Expand Up @@ -93,8 +98,11 @@ TFCallbackQueue >> initializeQueue [

| semaphoreIndex |

semaphoreIndex := Smalltalk registerExternalObject: semaphore.
self primitiveInitializeQueueWith: semaphoreIndex
[ semaphoreIndex := Smalltalk registerExternalObject: semaphore.
self primitiveInitializeQueueWith: semaphoreIndex ]
onErrorDo: [ :e |
semaphoreIndex ifNotNil: [ Smalltalk unregisterExternalObject: semaphoreIndex ].
e pass]
]

{ #category : #private }
Expand Down Expand Up @@ -162,8 +170,9 @@ TFCallbackQueue >> shutDown [
{ #category : #'system startup' }
TFCallbackQueue >> startUp [

self initializeQueue.
self forkCallbackProcess
[self initializeQueue.
self forkCallbackProcess]
onErrorDo: [ self inform: 'The current VM does not support TFFI Callbacks. It will use the old implementation' ]
]

{ #category : #initialization }
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFCallbackSameProcessRunStrategy.class.st
@@ -1,3 +1,6 @@
"
I am a simple strategy to run the callbacks always in the same process.
"
Class {
#name : #TFCallbackSameProcessRunStrategy,
#superclass : #TFCallbackForkRunStrategy,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFCharType.class.st
@@ -1,3 +1,6 @@
"
I extend TFIntType to support Characters.
"
Class {
#name : #TFCharType,
#superclass : #TFIntType,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFDerivedType.class.st
@@ -1,3 +1,6 @@
"
TFFI supports complex types. I am the representation of those. I have a basic type and I handle the marshalling delegating to the basic type and doing the little adjustements needed for me.
"
Class {
#name : #TFDerivedType,
#superclass : #Object,
Expand Down
3 changes: 3 additions & 0 deletions src/ThreadedFFI/TFFIBackend.class.st
@@ -1,3 +1,6 @@
"
I am the FFI backend implemented by using TFFI
"
Class {
#name : #TFFIBackend,
#superclass : #FFIBackend,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFInvalidSessionCallbackReturn.class.st
@@ -1,3 +1,7 @@
"
I am an error that indicates the callback cannot return because the session where it was created it does not exist anymore.
The image has been saved and continue in a new session. The callback cannot return.
"
Class {
#name : #TFInvalidSessionCallbackReturn,
#superclass : #TFCallbackCannotReturn,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFMainThreadRunner.class.st
@@ -1,3 +1,7 @@
"
I run the callouts and callbacks in the main thread of the process.
It can be or not the VM thread. It depends how the VM has been started.
"
Class {
#name : #TFMainThreadRunner,
#superclass : #TFRunner,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFOOPType.class.st
@@ -1,3 +1,7 @@
"
I know how to handle the case when we want to send a Pharo object to the FFI.
"
Class {
#name : #TFOOPType,
#superclass : #TFDerivedType,
Expand Down
4 changes: 4 additions & 0 deletions src/ThreadedFFI/TFPointerToStructType.class.st
@@ -1,3 +1,7 @@
"
I am a pointer to an Struct. I know how to reconstruct the struct from the received pointer and how to extract the pointer.
The pointer maybe is in the heap of Pharo (it is a ByteArray)
"
Class {
#name : #TFPointerToStructType,
#superclass : #TFDerivedType,
Expand Down

0 comments on commit c55234b

Please sign in to comment.