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/SIPCall.st

377 lines
12 KiB
Smalltalk

"
(C) 2011 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/>.
"
SIPRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logError: ('SIPCall(<1s>) got unhandled request <2p>.'
expandMacrosWithArguments: {aCall callId. self class verb}) area: #sip.
]
]
SIPByeRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logDebug: ('SIPCall(<1s>) got BYE.' expandMacrosWith: aCall callId) area: #sip.
aCall remoteHangup: self.
]
]
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am the base for sessions. I am a bit backward as the
Dialog will create/hold the session but we start with the session here
as this is what we are really interested in. So this is not really a
session as of the RFC... but at some stage in the exchange we will be
a proper session.'>
SIPSessionBase class >> on: aDialog useragent: aUseragent [
<category: 'creation'>
^ self new
useragent: aUseragent;
initialDialog: aDialog;
yourself
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog.
initial_dialog contact: ('sip:osmo_st_sip@<1p>:<2p>'
expandMacrosWith: ua transport address with: ua transport port).
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
callId [
<category: 'info'>
^ initial_dialog callId
]
check: aDialog [
<category: 'private'>
"I check if this enters a new confirmed dialog or if this is the
confirmed dialog."
"We have no confirmed dialog, accept it"
^ dialog isNil
ifTrue: [
aDialog isConfirmed ifTrue: [
dialog := aDialog.
self registerDialog.
self logNotice: ('SIPCall(<1s>) dialog is confirmed now.'
expandMacrosWith: self callId) area: #sip.
].
true]
ifFalse: [
"We could fork things here. For multi party call"
dialog to_tag = aDialog to_tag].
]
registerDialog [
<category: 'session'>
ua registerDialog: self.
]
unregisterDialog [
<category: 'session'>
rem isNil ifTrue: [
rem := Osmo.TimerScheduler instance
scheduleInSeconds: 60 block: [
ua unregisterDialog: self.
]]
]
nextCSeq [
| res |
<category: 'accessing'>
res := next_cseq.
next_cseq := next_cseq + 1.
^ res
]
isCompatible: aDialog [
<category: 'dialog'>
^ dialog isNil
ifTrue: [initial_dialog isCompatible: aDialog]
ifFalse: [dialog isCompatible: aDialog].
]
newRequest: aRequest [
<category: 'dialog'>
self logError: ('<1p>(<2s>) unhandled request <3p>.'
expandMacrosWithArguments: {self class. self callId. aRequest class verb})
area: #sip.
]
]
SIPSessionBase subclass: SIPCall [
| sdp_offer sdp_result invite state |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am a high level class to deal with transactions,
sessions and calls. Right now I do not support forking proxies and
will simply ignore everything but the first dialog.'>
SIPCall class >> stateInitial [ <category: 'states'> ^ #initial ]
SIPCall class >> stateInvite [ <category: 'states'> ^ #invite ]
SIPCall class >> stateSession [ <category: 'states'> ^ #session ]
SIPCall class >> stateTimeout [ <category: 'states'> ^ #timeout ]
SIPCall class >> stateCancel [ <category: 'states'> ^ #cancel ]
SIPCall class >> stateHangup [ <category: 'states'> ^ #hangup ]
SIPCall class >> stateRemoteHangup [ <category: 'states'> ^ #remoteHangup ]
SIPCall class >> stateFailed [ <category: 'states'> ^ #failed ]
LegalStates := nil.
SIPCall class >> legalStates [
<category: 'states'>
^ LegalStates ifNil: [
LegalStates := {
self stateInitial -> self stateInvite.
self stateInvite -> self stateSession.
self stateInvite -> self stateTimeout.
self stateInvite -> self stateCancel.
self stateInvite -> self stateFailed.
self stateSession -> self stateHangup.
self stateSession -> self stateRemoteHangup.
}
]
]
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
<category: 'creation'>
^ self
on: ((SIPDialog fromUser: aUser host: aHost port: aPort)
to: aTo; yourself) useragent: aUseragent
]
state [
<category: 'states'>
^ state ifNil: [self class stateInitial]
]
moveToState: aState [
<category: 'states'>
"E.g. we get two remote hang ups as our ack has not arrived."
self state = aState ifTrue: [^true].
"Check if there is a state transition"
(self class legalStates includes: (self state -> aState)) ifFalse: [
self logError: ('SIPCall(<1s>) transition <2p>-><3p> is not legal.'
expandMacrosWithArguments: {self callId. self state. aState})
area: #sip.
^ false
].
state := aState.
^ true
]
createCall: aSDPOffer [
<category: 'call'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: ('SIPCall(<1s>) failed to start.' expandMacrosWith: self callId)
area: #sip.
^ false
].
sdp_offer := aSDPOffer.
next_cseq := initial_dialog cseq + 1.
invite := (SIPInviteTransaction createWith: initial_dialog on: ua with: aSDPOffer cseq: initial_dialog cseq)
onTimeout: [self callTimedOut];
onSuccess: [:response :dialog | self callSuccess: response dialog: dialog];
onFailure: [:response :dialog | self callFailure: response dialog: dialog];
onNotification: [:response :dialog | self callNotification: response dialog: dialog];
start;
yourself
]
cancel [
<category: 'call'>
(self moveToState: self class stateCancel) ifTrue: [
self logNotice: ('SIPCall(<1s>) going to cancel it.' expandMacrosWith: self callId)
area: #sip.
self unregisterDialog.
invite cancel.
^ true
].
^ false
]
hangup [
<category: 'call'>
(self moveToState: self class stateHangup) ifTrue: [
self logNotice: ('SIPCall(<1s>) going to hangup.' expandMacrosWith: self callId)
area: #sip.
self unregisterDialog.
(SIPByeTransaction createWith: dialog on: ua cseq: self nextCSeq)
onTimeout: [self hangupTimedOut];
onSuccess: [:resp :dlg | self hangupSuccess: resp dialog: dlg];
onFailure: [:resp :dlg | self hangupFailure: resp dialog: dlg];
start
].
]
callTimedOut [
<category: 'call-result'>
self logError: ('SIPCall(<1s>) timed-out.' expandMacrosWith: self callId)
area: #sip.
(self moveToState: self class stateTimeout) ifFalse: [
invite := nil.
^ self logError: ('SIPCall(<1s>) failed to move to timeout.'
expandMacrosWith: self callId) area: #sip.
].
]
callSuccess: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCall(<1s>) can only have one session. Ignoring.'
expandMacrosWith: self callId) area: #sip.
^ false
].
(self moveToState: self class stateSession) ifTrue: [
self logNotice: ('SIPCall(<1s>) session established.'
expandMacrosWith: self callId) area: #sip.
sdp_result := aResponse sdp.
self sessionNew.
invite := nil.
^ true
].
^ false
]
callFailure: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCall(<1s>) can only have one session. Ignoring failure.'
expandMacrosWith: self callId) area: #sip.
^ false
].
(self moveToState: self class stateFailed) ifTrue: [
invite := nil.
self logNotice: ('SIPCall(<1s>) call failure.'
expandMacrosWith: self callId) area: #sip.
self sessionFailed.
].
]
callNotification: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCall(<1s>) can only have one session. Ignoring notification.'
expandMacrosWith: self callId) area: #sip.
^ false
].
self logNotice: ('SIPCall(<1s>) notification.'
expandMacrosWith: self callId) area: #sip.
self sessionNotification: aResponse.
]
hangupTimedOut [
<category: 'hangup-result'>
self logNotice: ('SIPCall(<1s>) hang-up timedout.'
expandMacrosWith: self callId) area: #sip.
]
hangupSuccess: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCall(<1s>) can only have one session. Ignoring failure.'
expandMacrosWith: self callId) area: #sip.
^ false
].
self logNotice: ('SIPCall(<1s>) hang-up success.'
expandMacrosWith: self callId) area: #sip.
]
hangupFailure: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCall(<1s>) can only have one session. Ignoring failure.'
expandMacrosWith: self callId) area: #sip.
^ false
].
self logNotice: ('SIPCall(<1s>) hang-up failure.'
expandMacrosWith: self callId) area: #sip.
]
remoteHangup: aRequest [
<category: 'remote-hangup'>
(self moveToState: self class stateRemoteHangup) ifTrue: [
self logNotice: ('SIPCall(<1s>) session remotely terminated.'
expandMacrosWith: self callId) area: #sip.
ua respondWith: 200 phrase: 'OK' on: aRequest dialog: dialog.
self unregisterDialog.
self sessionEnd.
].
]
terminate [
<category: 'public'>
"I try to finish up things."
self state = self class stateInvite ifTrue: [^self cancel].
self state = self class stateSession ifTrue: [^self hangup].
self logError: ('SIPCall(<1s>) terminate not possible in <2p>.'
expandMacrosWithArguments: {self callId. self state})
area: #sip.
]
sessionNew [
<category: 'callback'>
]
sessionFailed [
<category: 'callback'>
]
sessionEnd [
<category: 'callback'>
]
sessionNotification: aNot [
<category: 'callback'>
]
newRequest: aRequest [
<category: 'private'>
aRequest sipCallDispatch: self.
]
]