From d188d2afed8ae14b0ac9ed129befb72f6722ce8f Mon Sep 17 00:00:00 2001 From: Holger Hans Peter Freyther Date: Mon, 4 Jul 2011 22:30:14 +0200 Subject: [PATCH] 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. --- callagent/SIPCall.st | 158 +++++++++++++++++++++++++++++++++++++++++++ package.xml | 1 + 2 files changed, 159 insertions(+) create mode 100644 callagent/SIPCall.st diff --git a/callagent/SIPCall.st b/callagent/SIPCall.st new file mode 100644 index 0000000..7066596 --- /dev/null +++ b/callagent/SIPCall.st @@ -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 . +" + +Object subclass: SIPCall [ + | initial_dialog dialog sdp_offer invite state ua | + + + + SIPCall class >> stateInitial [ ^ #initial ] + SIPCall class >> stateInvite [ ^ #invite ] + SIPCall class >> stateSession [ ^ #session ] + SIPCall class >> stateTimeout [ ^ #timeout ] + SIPCall class >> stateCancel [ ^ #cancel ] + SIPCall class >> stateHangup [ ^ #hangup ] + SIPCall class >> stateRemoteHangup [ ^ #remoteHangup ] + + LegalStates := nil. + + SIPCall class >> legalStates [ + + ^ 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 [ + + ^ self new + initialDialog: ((SIPDialog fromUser: aUser host: aHost port: aPort) + to: aTo; yourself); + useragent: aUseragent; + yourself + ] + + state [ + + ^ state ifNil: [self class stateInitial] + ] + + moveToState: aState [ + + + "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 [ + + initial_dialog := aDialog + ] + + useragent: aUseragent [ + + ua := aUseragent + ] + + createCall: aSDPOffer [ + + 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 [ + + (self moveToState: self class stateCancel) ifTrue: [ + invite cancel. + ^ true + ]. + + ^ false + ] + + hangup [ + + (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 [ + + self logError: 'Call timed-out.' area: #sip. + ] + + callSuccess: aResponse dialog: aDialog [ + + self logError: 'Call session etsablished.' area: #sip. + ] + + callFailure: aResponse dialog: aDialog [ + + self logError: 'Call Failure.' area: #sip. + ] + + callNotification: aResponse dialog: aDialog [ + + self logError: 'Call Notification.' area: #sip. + ] + + hangupTimedOut [ + + self logError: 'Hang-Up timedout.' area: #sip. + ] + + hangupSuccess: aResponse dialog: aDialog [ + + self logError: 'Hang-Up success.' area: #sip. + ] + + hangupFailure: aResponse dialog: aDialog [ + + self logError: 'Hang-Up failure.' area: #sip. + ] +] diff --git a/package.xml b/package.xml index 2c6b005..543311e 100644 --- a/package.xml +++ b/package.xml @@ -5,6 +5,7 @@ grammar/SIPGrammar.st callagent/Base64MimeConverter.st + callagent/SIPCall.st callagent/SIPCallAgent.st callagent/SIPDialog.st callagent/SIPLogArea.st