summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-05-27 21:43:14 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-05-27 21:43:14 +0200
commit950be766f362cbebd288553833069bdbfa1115cf (patch)
tree59c80bba8ed37c1df5985c0b7540b1a792d6b497
parent6c2006b1ec4c107659fb210c04395a40985770c2 (diff)
-rw-r--r--callagent/session/SIPIncomingCall.st44
-rw-r--r--callagent/tests/SIPInviteTest.st39
2 files changed, 78 insertions, 5 deletions
diff --git a/callagent/session/SIPIncomingCall.st b/callagent/session/SIPIncomingCall.st
index a96cb4a..d9fe0cb 100644
--- a/callagent/session/SIPIncomingCall.st
+++ b/callagent/session/SIPIncomingCall.st
@@ -32,6 +32,7 @@ SIPCallBase subclass: SIPIncomingCall [
<category: 'states'>
^ LegalStates ifNil: [
LegalStates := {
+ self stateInvite -> self stateInvite.
self stateInvite -> self stateSession.
self stateInvite -> self stateRejected.
self stateInvite -> self stateFailed.
@@ -70,23 +71,58 @@ SIPCallBase subclass: SIPIncomingCall [
]
reject [
- | resp |
-
+ <category: 'accept'>
(self moveToState: self class stateRejected) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to reject.'
expandMacrosWith: self callId) area: #sip.
^false].
- resp := (SIPResponse code: 603 with: 'Not Found')
+ 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.
- self unregisterDialog.
]
remoteReInvite: aRequest dialog: aDialog [
diff --git a/callagent/tests/SIPInviteTest.st b/callagent/tests/SIPInviteTest.st
index 0d1c7d1..adf74f5 100644
--- a/callagent/tests/SIPInviteTest.st
+++ b/callagent/tests/SIPInviteTest.st
@@ -84,7 +84,7 @@ TestCase subclass: SIPInviteTest [
calls := 0.
- agent onNewCall: [:invite :dialog |
+ agent onNewCall: [:invite :dialog |
calls := calls + 1.
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
reject; yourself].
@@ -109,4 +109,41 @@ TestCase subclass: SIPInviteTest [
secondTag := (msg parameter: 'To' ifAbsent: []) tag.
self assert: firstTag equals: secondTag.
]
+
+ testConnectedCall [
+ | msg call |
+
+ agent onNewCall: [:invite :dialog |
+ call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
+ trying;
+ ringing;
+ pickUp: 'a SDP file';
+ yourself].
+
+ "Inject the invite"
+ transport inject: self createInvite.
+
+ "Check the reject"
+ self assert: sent size equals: 3.
+ msg := SIPParser parse: sent first data.
+ self assert: msg code equals: '100'.
+ self assert: msg phrase equals: 'Trying'.
+ self assert: agent dialogs size equals: 1.
+ self deny: call unregisterDialogIsPending.
+
+ msg := SIPParser parse: sent second data.
+ self assert: msg code equals: '180'.
+ self assert: msg phrase equals: 'Ringing'.
+ self assert: agent dialogs size equals: 1.
+ self deny: call unregisterDialogIsPending.
+
+ msg := SIPParser parse: sent second data.
+ self assert: msg code equals: '200'.
+ self assert: msg phrase equals: 'OK'.
+ self assert: agent dialogs size equals: 1.
+ self deny: call unregisterDialogIsPending.
+
+ "Inject the ACK for the 200"
+
+ ]
]