smalltalk
/
osmo-st-sip
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-sip/callagent/session/SIPIncomingCall.st

135 lines
4.7 KiB
Smalltalk

"
(C) 2011-2014 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/>.
"
SIPCallBase subclass: SIPIncomingCall [
| branch |
<category: 'OsmoSIP-Callagent'>
<comment: 'I represent an incoming call. One can call trying
rining, pickedUp on me to establish the call. Once the final
ACK has arrived my session will be established.'>
LegalStates := nil.
SIPIncomingCall class >> stateRejected [ <category: 'states'> ^#rejected]
SIPIncomingCall class >> legalStates [
<category: 'states'>
^ LegalStates ifNil: [
LegalStates := {
self stateInvite -> self stateInvite.
self stateInvite -> self stateSession.
self stateInvite -> self stateRejected.
self stateInvite -> self stateFailed.
self stateRejected -> self stateRejected.
self stateSession -> self stateHangup.
self stateSession -> self stateRemoteHangup.
}
]
]
SIPIncomingCall class >> initWith: anInvite dialog: dialog on: anAgent [
^self new
initialize;
useragent: anAgent;
confirmDialog: dialog with: anInvite;
yourself
]
initialize [
state := self class stateInvite.
]
confirmDialog: aDialog with: aRequest [
| via newDialog |
"TODO: look at where the data was actually received!"
via := (aRequest parameter: 'Via' ifAbsent: []).
branch := via branch.
newDialog := (SIPDialog localFromMessage: aRequest)
destIp: via address;
destPort: via port;
confirm;
yourself.
initial_dialog := newDialog.
dialog := newDialog.
self registerDialog.
]
reject [
<category: 'accept'>
(self moveToState: self class stateRejected) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to reject.'
expandMacrosWith: self callId) area: #sip.
^false].
self sendResponse: 603 text: 'Not Found' data: nil.
self unregisterDialog.
]
trying [
<category: 'accept'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to send invite'
expandMacrosWith: self callId) area: #sip.
^false].
self sendResponse: 100 text: 'Trying' data: nil.
]
ringing [
<category: 'accept'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to send ringing'
expandMacrosWith: self callId) area: #sip.
^false].
self sendResponse: 180 text: 'Ringing' data: nil.
]
pickUp: aSDPFile [
<category: 'accept'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to send ringing'
expandMacrosWith: self callId) area: #sip.
^false].
self sendResponse: 200 text: 'OK' data: aSDPFile.
]
sendResponse: aCode text: aText data: aFile [
| resp |
resp := (SIPResponse code: aCode with: aText)
addParameter: 'Via' value: (ua generateVia: branch);
addParameter: 'From' value: dialog generateFrom;
addParameter: 'To' value: dialog generateTo;
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: dialog cseq with: 'INVITE');
sdp: aFile;
yourself.
ua queueData: resp asDatagram dialog: dialog.
]
remoteReInvite: aRequest dialog: aDialog [
self state = self class stateRejected
ifTrue: [^self reject].
^self error: ('SIPIncomingCall(<1s>) unknown action for state <2s>'
expandMacrosWith: self callId with: self state) area: #sip.
]
]