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

callagent: Introduce high level SIP Call

Introduce a high level class that can create multiple transactions,
handles the sequence numbers, the dialogs, the opened session and
provides a nice call, hangup, cancel, terminate interface.
This commit is contained in:
Holger Hans Peter Freyther 2011-07-04 22:30:14 +02:00
parent 44bea36041
commit d188d2afed
2 changed files with 159 additions and 0 deletions

158
callagent/SIPCall.st Normal file
View File

@ -0,0 +1,158 @@
"
(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/>.
"
Object subclass: SIPCall [
| initial_dialog dialog sdp_offer invite state ua |
<category: 'SIP-Call'>
<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 ]
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 stateSession -> self stateHangup.
self stateSession -> self stateRemoteHangup.
}
]
]
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
<category: 'creation'>
^ self new
initialDialog: ((SIPDialog fromUser: aUser host: aHost port: aPort)
to: aTo; yourself);
useragent: aUseragent;
yourself
]
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: [^self].
"Check if there is a state transition"
(self class legalStates includes: (self state -> aState)) ifFalse: [
self logError: 'State transition %1->2 is not legal' % {self state. aState} area: #sip.
^ false
].
state := aState.
^ true
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
createCall: aSDPOffer [
<category: 'call'>
sdp_offer := aSDPOffer.
invite := (SIPInviteTransaction createWith: initial_dialog on: ua with: aSDPOffer)
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: [
invite cancel.
^ true
].
^ false
]
hangup [
<category: 'call'>
(self moveToState: self class stateHangup) ifTrue: [
(SIPByeTransaction createWith: dialog on: ua)
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: 'Call timed-out.' area: #sip.
]
callSuccess: aResponse dialog: aDialog [
<category: 'call-result'>
self logError: 'Call session etsablished.' area: #sip.
]
callFailure: aResponse dialog: aDialog [
<category: 'call-result'>
self logError: 'Call Failure.' area: #sip.
]
callNotification: aResponse dialog: aDialog [
<category: 'call-result'>
self logError: 'Call Notification.' area: #sip.
]
hangupTimedOut [
<category: 'hangup-result'>
self logError: 'Hang-Up timedout.' area: #sip.
]
hangupSuccess: aResponse dialog: aDialog [
<category: 'hangup-result'>
self logError: 'Hang-Up success.' area: #sip.
]
hangupFailure: aResponse dialog: aDialog [
<category: 'hangup-result'>
self logError: 'Hang-Up failure.' area: #sip.
]
]

View File

@ -5,6 +5,7 @@
<filein>grammar/SIPGrammar.st</filein>
<filein>callagent/Base64MimeConverter.st</filein>
<filein>callagent/SIPCall.st</filein>
<filein>callagent/SIPCallAgent.st</filein>
<filein>callagent/SIPDialog.st</filein>
<filein>callagent/SIPLogArea.st</filein>