smalltalk
/
osmo-st-core
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-core/Dispatcher.st

90 lines
2.5 KiB
Smalltalk

"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: Dispatcher [
| queue dispatch quit |
<category: 'OsmoCore-Core'>
<comment: 'I run tasks from the same context.'>
Dispatcher class >> instance [
<category: 'singleton'>
^ Smalltalk at: #OsmoDispatcher ifAbsent: [self install].
]
Dispatcher class >> new [
<category: 'private'>
^super new
addToBeFinalized;
startDispatching;
yourself
]
Dispatcher class >> install [
<category: 'singleton'>
| dispatcher |
dispatcher := Smalltalk at: #OsmoDispatcher ifAbsentPut: [self new].
^dispatcher class = self
ifTrue: [dispatcher]
ifFalse: [
dispatcher terminate.
Smalltalk at: #OsmoDispatcher put: self new]
]
startDispatching [
<category: 'private'>
quit := false.
queue := SharedQueue new.
dispatch := [
Processor activeProcess name: 'OsmoDispatcher'.
[quit]
whileFalse: [
self dispatch]
] forkAt: Processor highIOPriority.
]
dispatchBlock: aBlock [
<category: 'insert'>
queue nextPut: aBlock.
]
dispatch [
| block sem |
block := queue next.
sem := Semaphore new.
"Run the code in a new process as the debugger might terminate this
and then the dispatcher would not dispatch anymore. Use a Semaphore
to make sure we keep on processing items in order."
[[
block on: Error do: [:error |
error logException: ('dispatch failed on "', block printString, '".') area: #core.
]] ensure: [sem signal]] fork.
sem wait.
]
terminate [
<category: 'private'>
dispatch terminate
]
]
Eval [
Dispatcher instance.
]