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

callagent: Work on re-creating the socket after image resume

Use the same approach as with the SIP UDP Transport to close the
socket and terminate the two handlers. This way both processes are
stopped at the end of the session.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-09 01:15:26 +02:00
parent e21595dafe
commit e3c2bcf1ca
1 changed files with 45 additions and 18 deletions

View File

@ -19,7 +19,7 @@
PackageLoader fileInPackage: 'Sockets'.
Object subclass: MGCPCallAgentBase [
| socket queue rx tx trunks sem addr port |
| socket queue rx tx trunks sem addr port net_exit |
<category: 'MGCP-Callagent'>
<comment: 'I am responsible for the networking'>
@ -44,6 +44,7 @@ Object subclass: MGCPCallAgentBase [
trunks := OrderedCollection new.
addr := anAddress.
port := aPort.
net_exit := Semaphore new.
]
addTrunk: aTrunk [
@ -68,29 +69,55 @@ Object subclass: MGCPCallAgentBase [
"Receive datagrams from the socket..."
rx := [
Processor activeProcess name: 'MGCP RX'.
[ | data |
data := socket next.
data ifNotNil: [
OsmoDispatcher dispatchBlock: [self handleData: data].
].
] repeat.
] fork.
[Processor activeProcess name: 'MGCP RX'.
self runRXProcess] ensure: [net_exit signal]] fork.
"Send data to the MGWs"
tx := [
Processor activeProcess name: 'MGCP TX'.
[ | data |
data := queue next.
socket nextPut: data.
] repeat.
] fork.
[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 [
socket ifNotNil: [socket close].
tx ifNotNil: [tx terminate].
rx ifNotNil: [rx terminate].
socket ifNil: [^self].
"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 [