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

timer: Another approach to fix the issues on Pharo

Pharo's DateAndTime/Delay and VM interaction is bogus. If we execute
DateAndTime/Delay too early things will get stuck and take 100% of
the CPU.
This commit is contained in:
Holger Hans Peter Freyther 2014-02-12 17:15:20 +01:00
parent 3e2be093de
commit ed74b0c1ca
2 changed files with 28 additions and 29 deletions

View File

@ -67,7 +67,7 @@ Object subclass: Timer [
]
Object subclass: TimerScheduler [
| queue sem loop quit lastDelay |
| queue sem loop quit processExited |
<category: 'OsmoCore-Timer'>
<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
@ -94,26 +94,21 @@ bit difficult to do this race free.'>
quit := true.
]
platformInit [
<category: 'creation'>
"Nothing for GST..."
]
initialize [
<category: 'private'>
queue := SortedCollection sortBlock: [:a :b | a timeout < b timeout].
sem := Semaphore forMutualExclusion.
quit := false.
self
startLoop;
platformInit.
self startLoop.
]
startLoop [
<category: 'creation'>
loop := [Processor activeProcess name: 'Osmo Timers'.
self runTimers] fork.
processExited := Semaphore new.
loop := [[Processor activeProcess name: 'Osmo Timers'.
self runTimers
] ensure: [processExited signal. loop := nil]] fork
]
scheduleInSeconds: aDelay block: aBlock [
@ -135,12 +130,7 @@ bit difficult to do this race free.'>
<category: 'delay_loop'>
[quit] whileFalse: [ | now |
"Remember the last delay so we can interrupt it on image resume on Pharo"
lastDelay := Delay forSeconds: 1.
lastDelay wait.
lastDelay := nil.
(Delay forSeconds: 1) wait.
now := DateTime now.
OsmoDispatcher dispatchBlock: [self fireTimers: now].
]

View File

@ -1,25 +1,34 @@
TimerScheduler extend [
TimerScheduler class >> initialize [
<category: 'loading'>
^ self instance
"Pharo requires us to do some post-processing"
Smalltalk addToStartUpList: self.
Smalltalk addToShutDownList: self.
^self instance.
]
TimerScheduler class >> startUp [
Smalltalk at: #OsmoTimeScheduler ifPresent: [
OsmoTimeScheduler reinitialize.
].
Smalltalk at: #OsmoTimeScheduler ifPresent: [:timer | timer doStartUp].
]
platformInit [
<category: 'creation'>
"Pharo requires us to do some post-processing"
Smalltalk addToStartUpList: self class.
TimerScheduler class >> shutDown: quitting [
Smalltalk at: #OsmoTimeScheduler ifPresent: [:timer | timer doShutDown].
]
reinitialize [
<category: 'creation'>
"(Delay forSeconds: 1) wait can get stuck in Pharo for-ever.. Change the approach"
lastDelay ifNotNil: [lastDelay signalWaitingProcess]
doShutDown [
<category: 'PharoHacks'>
loop ifNil: [^self].
quit := true.
processExited wait.
Transcript nextPutAll: 'Stopped the TimerScheduler process'; cr.
]
doStartUp [
<category: 'PharoHacks'>
loop ifNotNil: [^self error: 'The loop should have vanished'].
Transcript nextPutAll: 'Starting the TimerScheduler loop again'; cr.
quit := false.
self startLoop.
]
]