smalltalk
/
osmo-st-core
Archived
1
0
Fork 0

timer: Prevent a potential race with the loop process resumption

It is possible that the "loop" has determined there are no pending
timers but then the insertion application is executing and is
inserting a timer. Once the loop is executing again it will sleep
as there was no timer and we will miss the wake-up until there is
another timer.
This commit is contained in:
Holger Hans Peter Freyther 2014-07-27 10:19:25 +02:00
parent 5c7b52662c
commit f2be904848
2 changed files with 18 additions and 13 deletions

View File

@ -73,7 +73,7 @@ Object subclass: Timer [
] ]
Object subclass: TimerScheduler [ Object subclass: TimerScheduler [
| queue sem loop quit processExited delay | | queue sem loop quit processExited delay loopSem |
<category: 'OsmoCore-Timer'> <category: 'OsmoCore-Timer'>
<comment: 'I can help to fire things at the right time. Right now I <comment: 'I can help to fire things at the right time. Right now I
only work on seconds granularity because Time has no direct access to only work on seconds granularity because Time has no direct access to
@ -108,7 +108,8 @@ bit difficult to do this race free.'>
"Nothing for GST" "Nothing for GST"
loop ifNil: [^self]. loop ifNil: [^self].
quit := true. quit := true.
loop isSuspended ifTrue: [loop resume]. sem critical: [
loopSem ifNotNil: [loopSem signal]].
delay ifNotNil: [:the_delay | the_delay signal]. delay ifNotNil: [:the_delay | the_delay signal].
processExited wait. processExited wait.
Transcript nextPutAll: 'Stopped the TimerScheduler process'; cr Transcript nextPutAll: 'Stopped the TimerScheduler process'; cr
@ -158,15 +159,14 @@ bit difficult to do this race free.'>
sem critical: [ sem critical: [
currentFirst := queue isEmpty ifFalse: [queue first]. currentFirst := queue isEmpty ifFalse: [queue first].
queue add: timer. queue add: timer.
loop isSuspended
ifTrue: [loop resume]
ifFalse: [
"if the first item in the queue has changed we need to readjust the delay
to wait for. Signalling the waiting delay will enter the recalculation of a new
expire time"
currentFirst == queue first "Make sure the loopSem is waking up at least once."
ifFalse: [self signalDelay]]]. loopSem ifNotNil: [loopSem signal].
"if the first item in the queue has changed we need to readjust the delay
to wait for. Signalling the waiting delay will enter the recalculation of
a new expire time"
currentFirst == queue first
ifFalse: [self signalDelay]].
^timer ^timer
] ]
@ -180,7 +180,11 @@ bit difficult to do this race free.'>
[quit] whileFalse: [ [quit] whileFalse: [
| timer | | timer |
sem critical: [queue isEmpty ifFalse: [timer := queue first]]. sem critical: [
queue isEmpty ifFalse: [timer := queue first].
loopSem := Semaphore new.
].
timer isNil timer isNil
ifTrue: [ ifTrue: [
"nothing to do. No need to poll an empty queue. Remove delay to get rid of "nothing to do. No need to poll an empty queue. Remove delay to get rid of
@ -189,7 +193,7 @@ bit difficult to do this race free.'>
hold here." hold here."
delay := nil. delay := nil.
loop suspend] loopSem wait]
ifFalse: [ ifFalse: [
"either a timer has expired and we process it or we wait for the first item in "either a timer has expired and we process it or we wait for the first item in
the queue to expire" the queue to expire"

View File

@ -19,7 +19,8 @@ TimerScheduler extend [
<category: 'PharoHacks'> <category: 'PharoHacks'>
loop ifNil: [^self]. loop ifNil: [^self].
quit := true. quit := true.
loop isSuspended ifTrue: [loop resume]. sem critical: [
loopSem ifNotNil: [loopSem signal]].
delay ifNotNil: [:the_delay | the_delay signalWaitingProcess]. delay ifNotNil: [:the_delay | the_delay signalWaitingProcess].
processExited wait. processExited wait.
Transcript Transcript