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

invite: Create a base class for the "call"

I nee to differentiate between incoming and outgoing calls. At
the same time a lot of logic can be shared. Specially at the
time the call is established the hangup will work the same on
both sides.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-27 17:36:34 +02:00
parent 77ef4b6ece
commit 69810d6afa
3 changed files with 139 additions and 108 deletions

View File

@ -16,22 +16,13 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
SIPSessionBase subclass: SIPCall [
| sdp_offer sdp_result invite state |
SIPCallBase subclass: SIPCall [
| sdp_offer sdp_result invite |
<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 ]
SIPCall class >> stateRedirect [ <category: 'states'> ^ #redirect ]
LegalStates := nil.
@ -61,29 +52,6 @@ will simply ignore everything but the first dialog.'>
^self fromIdenity: aUser identity: aUseragent mainIdentity host: aHost port: aPort to: aTo on: 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'>
@ -120,21 +88,6 @@ will simply ignore everything but the first dialog.'>
^ 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)
@ -201,53 +154,11 @@ will simply ignore everything but the first dialog.'>
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.
]
remoteReInvite: aRequest dialog: aDialog [
"TODO: check if we are in a session..."
ua respondWith: 200 phrase: 'OK' on: aRequest dialog: aDialog.
]
remoteHangup: aRequest dialog: aDialog [
<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: aDialog.
self unregisterDialog.
self sessionEnd.
].
]
terminate [
<category: 'public'>
"I try to finish up things."
@ -275,33 +186,16 @@ will simply ignore everything but the first dialog.'>
^true.
]
sessionNew [
<category: 'callback'>
]
sessionFailed [
<category: 'callback'>
]
sessionRedirect: aContact [
<category: 'callback'>
"Legacy support to just fail"
^self sessionFailed
]
sessionEnd [
<category: 'callback'>
]
sessionNotification: aNot [
<category: 'callback'>
]
newRequest: aRequest dialog: aDialog [
<category: 'private'>
aRequest sipCallDispatch: self dialog: aDialog.
]
extractContact: aResponse [
| contact |
contact := aResponse parameter: 'Contact'.

View File

@ -0,0 +1,136 @@
"
(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/>.
"
SIPSessionBase subclass: SIPCallBase [
| state |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am the base class for incoming and outgoing
sessions (calls). The common code goes here'>
SIPCallBase class >> stateInitial [ <category: 'states'> ^ #initial ]
SIPCallBase class >> stateInvite [ <category: 'states'> ^ #invite ]
SIPCallBase class >> stateSession [ <category: 'states'> ^ #session ]
SIPCallBase class >> stateTimeout [ <category: 'states'> ^ #timeout ]
SIPCallBase class >> stateCancel [ <category: 'states'> ^ #cancel ]
SIPCallBase class >> stateHangup [ <category: 'states'> ^ #hangup ]
SIPCallBase class >> stateRemoteHangup [ <category: 'states'> ^ #remoteHangup ]
SIPCallBase class >> stateFailed [ <category: 'states'> ^ #failed ]
SIPCallBase class >> stateRedirect [ <category: 'states'> ^ #redirect ]
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: ('SIPCallBase(<1s>) transition <2p>-><3p> is not legal.'
expandMacrosWithArguments: {self callId. self state. aState})
area: #sip.
^ false
].
state := aState.
^ true
]
hangup [
<category: 'call'>
(self moveToState: self class stateHangup) ifTrue: [
self logNotice: ('SIPCallBase(<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
].
]
hangupTimedOut [
<category: 'hangup-result'>
self logNotice: ('SIPCallBase(<1s>) hang-up timedout.'
expandMacrosWith: self callId) area: #sip.
]
hangupSuccess: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCallBase(<1s>) can only have one session. Ignoring failure.'
expandMacrosWith: self callId) area: #sip.
^ false
].
self logNotice: ('SIPCallBase(<1s>) hang-up success.'
expandMacrosWith: self callId) area: #sip.
]
hangupFailure: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: ('SIPCallBase(<1s>) can only have one session. Ignoring failure.'
expandMacrosWith: self callId) area: #sip.
^ false
].
self logNotice: ('SIPCallBase(<1s>) hang-up failure.'
expandMacrosWith: self callId) area: #sip.
]
remoteHangup: aRequest dialog: aDialog [
<category: 'remote-hangup'>
(self moveToState: self class stateRemoteHangup) ifTrue: [
self logNotice: ('SIPCallBase(<1s>) session remotely terminated.'
expandMacrosWith: self callId) area: #sip.
ua respondWith: 200 phrase: 'OK' on: aRequest dialog: aDialog.
self unregisterDialog.
self sessionEnd.
].
]
newRequest: aRequest dialog: aDialog [
<category: 'private'>
aRequest sipCallDispatch: self dialog: aDialog.
]
sessionNew [
<category: 'callback'>
"Add custom handling"
]
sessionFailed [
<category: 'callback'>
"Add custom handling"
]
sessionEnd [
<category: 'callback'>
"Add custom handling"
]
]

View File

@ -51,6 +51,7 @@
<filein>callagent/session/Extensions.st</filein>
<filein>callagent/session/SIPSessionBase.st</filein>
<filein>callagent/session/SIPCallBase.st</filein>
<filein>callagent/session/SIPCall.st</filein>
<filein>callagent/transport/SIPTransport.st</filein>