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-network/osmo/OsmoUDPSocket.st

115 lines
2.8 KiB
Smalltalk

"
(C) 2010-2012 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: OsmoUDPSocket [
| socket queue rx tx net_exit name on_data |
<category: 'OsmoNetwork-Socket'>
<comment: 'I help in sending and dispatching UDP messages. I will
start two processes for socket handling.'>
OsmoUDPSocket class >> new [
<category: 'creation'>
^self basicNew initialize
]
initialize [
<category: 'creation'>
queue := SharedQueue new.
net_exit := Semaphore new.
]
name: aName [
<category: 'creation'>
name := aName
]
onData: aBlock [
<category: 'creation'>
on_data := aBlock
]
start: aSocket [
<category: 'creation'>
socket := aSocket.
"Receive datagrams from the socket..."
rx := self startRXProcess.
"Send data to the MGWs"
tx := [
[Processor activeProcess name: name, ' TX'.
self runTXProcess] ensure: [net_exit signal]] fork.
]
startRXProcess [
^ [[Processor activeProcess name: name, ' RX'.
self runRXProcess] ensure: [net_exit signal]] fork.
]
runRXProcess [
<category: 'processing'>
[ | data |
socket ensureReadable.
socket isOpen ifFalse: [
^self logNotice: name, ' socket closed.' area: #core].
data := socket next.
on_data value: data.
] repeat.
]
runTXProcess [
<category: 'processing'>
[ | data |
data := queue next.
data = nil ifTrue: [
^self logNotice: name, ' TX asked to quit.' area: #core].
socket nextPut: data.
] repeat.
]
stop [
<category: 'processing'>
socket ifNil: [^self].
"Close"
socket close.
queue nextPut: nil.
"Wait for the process to exit"
self logNotice: name, ' waiting for IO handlers to exit.' area: #core.
net_exit
wait;
wait.
"Forget things"
socket := nil.
tx := nil.
rx := nil.
]
queueData: aData [
<category: 'sending'>
queue nextPut: aData
]
]