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

mgcp: Use the common UDPSocket code to reduce the complexity

This commit is contained in:
Holger Hans Peter Freyther 2012-08-09 02:15:23 +02:00
parent e3c2bcf1ca
commit ca0d7624a8
1 changed files with 15 additions and 53 deletions

View File

@ -16,10 +16,12 @@
along with this program. If not, see <http://www.gnu.org/licenses/>. along with this program. If not, see <http://www.gnu.org/licenses/>.
" "
PackageLoader fileInPackage: 'Sockets'. PackageLoader
fileInPackage: 'Sockets';
fileInPackage: 'OsmoNetwork'.
Object subclass: MGCPCallAgentBase [ Object subclass: MGCPCallAgentBase [
| socket queue rx tx trunks sem addr port net_exit | | net trunks sem addr port |
<category: 'MGCP-Callagent'> <category: 'MGCP-Callagent'>
<comment: 'I am responsible for the networking'> <comment: 'I am responsible for the networking'>
@ -40,11 +42,14 @@ Object subclass: MGCPCallAgentBase [
initialize: anAddress port: aPort [ initialize: anAddress port: aPort [
<category: 'creation'> <category: 'creation'>
sem := Semaphore forMutualExclusion. sem := Semaphore forMutualExclusion.
queue := SharedQueue new.
trunks := OrderedCollection new. trunks := OrderedCollection new.
addr := anAddress. addr := anAddress.
port := aPort. port := aPort.
net_exit := Semaphore new.
net := Osmo.OsmoUDPSocket new
name: 'MGCPCallAgent';
onData: [:data | OsmoDispatcher dispatchBlock: [self handleData: data]];
yourself.
] ]
addTrunk: aTrunk [ addTrunk: aTrunk [
@ -60,6 +65,7 @@ Object subclass: MGCPCallAgentBase [
] ]
start [ start [
| socket |
<category: 'handling'> <category: 'handling'>
self stop. self stop.
@ -67,61 +73,17 @@ Object subclass: MGCPCallAgentBase [
bufferSize: 2048; bufferSize: 2048;
yourself. yourself.
"Receive datagrams from the socket..." net start: socket.
rx := [
[Processor activeProcess name: 'MGCP RX'.
self runRXProcess] ensure: [net_exit signal]] fork.
"Send data to the MGWs"
tx := [
[Processor activeProcess name: 'MGCP TX'.
self runTXProcess] ensure: [net_exit signal]] fork.
]
runRXProcess [
<category: 'processing'>
[ | data |
socket ensureReadable.
socket isOpen ifFalse: [
^self logNotice: 'MGCPCallAgent socket closed.' area: #mgcp].
OsmoDispatcher dispatchBlock: [self handleData: data].
] repeat.
]
runTXProcess [
<category: 'processing'>
[ | data |
data := queue next.
data = nil ifTrue: [
^self logNotice: 'MGCPCallAgent TX asked to quit.' area: #mgcp].
socket nextPut: data.
] repeat.
] ]
stop [ stop [
socket ifNil: [^self]. <category: 'processing'>
net stop
"Close"
socket close.
queue nextPut: nil.
"Wait for the process to exit"
self logNotice: 'MGCPCallAgent waiting for IO handlers to exit.' area: #mgcp.
net_exit
wait;
wait.
"Forget things"
socket := nil.
tx := nil.
rx := nil.
] ]
queueData: aDatagram [ queueData: aDatagram [
queue nextPut: aDatagram. <category: 'sending'>
net queueData: aDatagram.
] ]
] ]