Skip to content

Commit

Permalink
Adding a method to wait the gc only until the condition arrives.
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Apr 20, 2021
1 parent 7413173 commit dddfa98
Show file tree
Hide file tree
Showing 5 changed files with 68 additions and 60 deletions.
25 changes: 13 additions & 12 deletions src/TaskIt-Tests/TKTCommonQueueWorkerPoolTest.class.st
Expand Up @@ -70,45 +70,46 @@ TKTCommonQueueWorkerPoolTest >> testWorkerPoolStopStopsWorkers [

{ #category : #tests }
TKTCommonQueueWorkerPoolTest >> testWorkerPoolWorkersAreStoppedAfterPoolsCollection [
| pool workerProcess |

| pool workerProcess |
pool := TKTCommonQueueWorkerPool new.
pool name: 'test pool' , UUID new asString.
pool poolMaxSize: 4.
pool start.
(pool future: (MessageSend receiver: self selector: #yourself))
(pool future: (MessageSend receiver: self selector: #yourself))
waitForCompletion: 1 second.
self assert: pool workers notEmpty.
workerProcess := WeakArray with: pool workers anyOne process.
pool := nil.
self garbageCollectAndWait.
self assert: workerProcess first isNil

self assertWithGarbageCollect: [ workerProcess first isNil ].
]

{ #category : #tests }
TKTCommonQueueWorkerPoolTest >> testWorkerPoolWorkersProcessesAreStoppedAfterPoolsCollection [
| pool workerProcess |

| pool workerProcess |
pool := TKTCommonQueueWorkerPool new.
pool name: 'Test pool' , UUID new asString.
pool poolMaxSize: 4.
pool start.
(pool future: (MessageSend receiver: self selector: #yourself))
(pool future: (MessageSend receiver: self selector: #yourself))
waitForCompletion: 1 second.
workerProcess := WeakArray with: pool workers anyOne process process.
pool := nil.
self garbageCollectAndWait.
self assert: workerProcess first isNil
self assertWithGarbageCollect: [ workerProcess first isNil ].

]

{ #category : #tests }
TKTCommonQueueWorkerPoolTest >> testWorkerPoolWorkersProcessesAreTerminatedAfterPoolsCollection [

| pool workerProcess |
pool := TKTCommonQueueWorkerPool createDefault.
(pool future: (MessageSend receiver: self selector: #yourself)) waitForCompletion: 1 second.
(pool future: (MessageSend receiver: self selector: #yourself))
waitForCompletion: 1 second.
workerProcess := pool workers anyOne process process.
pool := nil.
self garbageCollectAndWait.
workerProcess isTerminated.
self assert: workerProcess isTerminated
self assertWithGarbageCollect: [ workerProcess isTerminated ].

]
11 changes: 3 additions & 8 deletions src/TaskIt-Tests/TKTMemoryLeakTest.class.st
Expand Up @@ -8,14 +8,9 @@ Class {
TKTMemoryLeakTest >> trackInstancesOf: aClass during: aBlock [

| before |

self garbageCollectAndWait .

before := aClass allInstances size.

aBlock value.

self garbageCollectAndWait .

self assert: before >= aClass allInstances size.

self assertWithGarbageCollect: [ before >= aClass allInstances size ].
]
32 changes: 20 additions & 12 deletions src/TaskIt-Tests/TKTTestCase.class.st
Expand Up @@ -8,18 +8,20 @@ Class {
}

{ #category : #running }
TKTTestCase >> garbageCollectAndWait [
5
timesRepeat: [ Smalltalk garbageCollect.
100 milliSeconds wait ].
" 1 second wait.
5
timesRepeat: [ Smalltalk garbageCollect.
100 milliSeconds wait ].
1 second wait.
5
timesRepeat: [ Smalltalk garbageCollect.
100 milliSeconds wait ]"
TKTTestCase >> assertWithGarbageCollect: aBlock [

| waitingPeriod timesToRun |

waitingPeriod := 100 milliSeconds.
timesToRun := self defaultTimeLimit / waitingPeriod.

timesToRun timesRepeat: [
aBlock value ifTrue: [ ^ self ].

Smalltalk garbageCollect.
waitingPeriod wait ].

self fail: 'Timeout waiting for ' , aBlock printString
]

{ #category : #running }
Expand All @@ -41,3 +43,9 @@ TKTTestCase >> tearDown [
TKTConfiguration resetSoleInstance.
super tearDown
]

{ #category : #running }
TKTTestCase >> waitGarbageCollect [

5 timesRepeat: [ Smalltalk garbageCollect. 100 milliSecond wait ]
]
30 changes: 13 additions & 17 deletions src/TaskIt-Tests/TKTWorkerPoolTest.class.st
Expand Up @@ -111,41 +111,37 @@ TKTWorkerPoolTest >> testWorkerPoolWorkersAreStoppedAfterPoolsCollection [
pool name: 'test pool'.
pool poolMaxSize: 4.
pool start.

(pool future: [ 1 ])
waitForCompletion: 1 second.

(pool future: [ 1 ]) waitForCompletion: 1 second.

self assert: pool workers notEmpty.

workerProcess := WeakArray with: pool workers anyOne process.

pool := nil.
self garbageCollectAndWait .

self assert: workerProcess first isNil.
pool := nil.
self assertWithGarbageCollect: [ workerProcess first isNil ].
]

{ #category : #tests }
TKTWorkerPoolTest >> testWorkerPoolWorkersProcessesAreStoppedAfterPoolsCollection [

| pool workerProcess |
pool := TKTWorkerPool new.
pool name: 'test pool'.
pool poolMaxSize: 4.
pool start.

(pool future: [ 1 ])
waitForCompletion: 1 second.

(pool future: [ 1 ]) waitForCompletion: 1 second.

workerProcess := WeakArray with: pool workers anyOne process process.

pool := nil.
self garbageCollectAndWait .

self assert: workerProcess first isNil
pool := nil.
self assertWithGarbageCollect: [ workerProcess first isNil ].
]

{ #category : #tests }
TKTWorkerPoolTest >> testWorkerPoolWorkersProcessesAreTerminatedAfterPoolsCollection [

| pool workerProcess |
pool := TKTWorkerPool new.
pool name: 'Test pool'.
Expand All @@ -154,6 +150,6 @@ TKTWorkerPoolTest >> testWorkerPoolWorkersProcessesAreTerminatedAfterPoolsCollec
(pool future: [ 1 ]) waitForCompletion: 1 second.
workerProcess := pool workers anyOne process process.
pool := nil.
self garbageCollectAndWait .
self assert: workerProcess isTerminated
self assertWithGarbageCollect: [ workerProcess isTerminated ].

]
30 changes: 19 additions & 11 deletions src/TaskIt-Tests/TKTWorkerTest.class.st
Expand Up @@ -34,56 +34,64 @@ TKTWorkerTest >> testWorkerProcessDiesAfterStop [

{ #category : #tests }
TKTWorkerTest >> testWorkerProcessDiesAfterWorkerAndAllFuturesAreCollected [

| worker future process waitFuture1 waitFuture2 |
worker := TKTWorker new.
worker start.
process := worker process.
waitFuture1 := TKTFuture
doing: [ [ process isRunning ] whileTrue: [ 50 milliSeconds wait ] ].
waitFuture2 := TKTFuture
doing: [ [ process isRunning ] whileTrue: [ 50 milliSeconds wait ] ].
waitFuture1 := TKTFuture doing: [
[ process isRunning ] whileTrue: [
50 milliSeconds wait ] ].
waitFuture2 := TKTFuture doing: [
[ process isRunning ] whileTrue: [
50 milliSeconds wait ] ].
future := worker future: [ 10 milliSeconds wait ].
worker := nil.
self garbageCollectAndWait.
self waitGarbageCollect.
self
should: [ waitFuture1 synchronizeTimeout: 200 milliSeconds ]
raise: TKTTimeoutException.
self assert: process isRunning.
future := nil.
self garbageCollectAndWait.
self garbageCollectAndWait.
self waitGarbageCollect.
self waitGarbageCollect.
waitFuture2 synchronizeTimeout: 400 milliSeconds.
self deny: process isRunning
]

{ #category : #tests }
TKTWorkerTest >> testWorkerProcessDiesAfterWorkerIsCollected [

| worker future process |
worker := TKTWorker new.
worker start.
process := worker process.
worker := nil.
self garbageCollectAndWait.
future := TKTFuture doing: [ [ process isRunning ] whileTrue: [ 50 milliSeconds wait ] ].
self waitGarbageCollect.
future := TKTFuture doing: [
[ process isRunning ] whileTrue: [ 50 milliSeconds wait ] ].
future synchronizeTimeout: 2 seconds.
self deny: process isRunning
]

{ #category : #tests }
TKTWorkerTest >> testWorkerProcessIsWorkingUntilAllTasksAreDone [

| worker process waitFuture |
worker := TKTWorker new.
worker start.
process := worker process.
waitFuture := TKTFuture doing: [ [ process isRunning ] whileTrue: [ 50 milliSeconds wait ] ].
waitFuture := TKTFuture doing: [
[ process isRunning ] whileTrue: [
50 milliSeconds wait ] ].
worker schedule: [ 100 milliSeconds wait ].
self assert: process taskQueue size equals: 1.
50 milliSeconds wait.
self assert: process taskQueue size equals: 0.
worker := nil.
self assert: process taskQueue size equals: 0.
self assert: process isRunning.
self garbageCollectAndWait .
self waitGarbageCollect.
waitFuture waitForCompletion: 100 second.
self deny: process isRunning
]
Expand Down

0 comments on commit dddfa98

Please sign in to comment.