smalltalk
/
osmo-st-all
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-all/osmo-st-mgcp/callagent/MGCPTransaction.st

229 lines
6.0 KiB
Smalltalk

"
(C) 2011-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/>.
"
PackageLoader
fileInPackage: 'Sockets';
fileInPackage: 'OsmoCore'.
Object subclass: MGCPTransactionBase [
| callagent t_retransmit t_expire t_remove sem |
<comment: 'I handle timers for the transaction'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransactionBase class >> on: aCallagent [
^ self new
initialize;
callagent: aCallagent;
yourself
]
MGCPTransactionBase class >> retransmitTime [ <category: 'timeouts'> ^ 10 ]
MGCPTransactionBase class >> expireTime [ <category: 'timeouts'> ^ 60 ]
MGCPTransactionBase class >> removeTime [ <category: 'timeouts'> ^ 3 * 60 ]
initialize [
<category: 'creation'>
sem := RecursionLock new.
]
callagent: aCallagent [
<category: 'private'>
callagent := aCallagent.
callagent addTransaction: self.
]
callagent [
<category: 'private'>
^ callagent
]
schedule: aTime block: aBlock [
<category: 'helper'>
^ Osmo.TimerScheduler instance scheduleInSeconds: aTime
block: aBlock.
]
startRetransmitTimer [
<category: 'private'>
sem critical: [
t_retransmit ifNotNil: [t_retransmit cancel].
t_retransmit := self schedule: self class retransmitTime
block: [self transactionRetransmit].
]
]
stopRetransmitTimer [
<category: 'private'>
sem critical: [
t_retransmit ifNotNil: [t_retransmit cancel].
]
]
started [
<category: 'public'>
t_expire := self schedule: self class expireTime
block: [self transactionExpired].
t_remove := self schedule: self class removeTime
block: [self transactionRemoved].
]
completed [
<category: 'public'>
sem critical: [
t_retransmit cancel.
t_expire cancel.
]
]
]
MGCPTransactionBase subclass: MGCPTransaction [
| result timeout id command endpoint state |
<comment: 'I am a transaction...'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransaction class >> on: endpoint of: callagent [
| res |
<category: 'factory'>
^ (self on: callagent)
instVarNamed: #endpoint put: endpoint;
yourself.
]
MGCPTransaction class >> stateInitial [ ^ 0 ]
MGCPTransaction class >> stateStarted [ ^ 1 ]
MGCPTransaction class >> stateFinished [ ^ 2 ]
transactionId [
<category: 'accessing'>
^ id
]
state [
<category: 'state'>
^ state ifNil: [state := self class stateInitial]
]
transactionId: anId [
<category: 'private'>
id := anId.
]
command [
<category: 'creation'>
^ command
]
command: aMGCPCommand [
<category: 'configuration'>
command := aMGCPCommand.
command transactionId: id.
command endpoint: endpoint endpointName.
]
onResult: aBlock [
<category: 'callback'>
result := aBlock
]
onTimeout: aBlock [
<category: 'callback'>
timeout := aBlock
]
start [
<category: 'network'>
state := self class stateStarted.
self started.
^ self sendData
]
startSingleShot [
<category: 'network'>
state := self class stateStarted.
self started.
^ self sendDataDirect
]
sendData [
<category: 'private'>
self startRetransmitTimer.
self sendDataDirect
]
sendDataDirect [
<category: 'private'>
| datagram |
datagram := Sockets.Datagram data: (command asDatagram)
address: (Sockets.SocketAddress
byName: endpoint trunk destIp)
port: 2427.
self callagent queueData: datagram.
]
response: aRes [
"Handle response but only once"
state = self class stateStarted ifFalse: [
^ self logError: 'Transaction(ID:%1 verb:%2) already terminated'
% {id. command class verb} area: #mgcp.
].
"Remember things for the future"
self logNotice: 'Transaction(ID:%1 verb:%2) got a response.'
% {id. command class verb} area: #mgcp.
state := self class stateFinished.
self completed.
"completed..."
result ifNotNil: [
result value: self value: aRes.
].
]
transactionRemoved [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) is finished. %3'
% {id. command class verb. DateTime now} area: #mgcp.
self callagent removeTransactionInternal: self.
]
transactionExpired [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) expired. %3'
% {id. command class verb. DateTime now} area: #mgcp.
state := self class stateFinished.
self stopRetransmitTimer.
timeout ifNotNil: [
timeout value: self.
]
]
transactionRetransmit [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) retransmit.'
% {id. command class verb} area: #mgcp.
self sendData.
]
]