summaryrefslogtreecommitdiffstats
path: root/callagent
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-03-25 09:40:26 +0100
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-03-25 12:59:26 +0100
commit2020d4cdf4363f176374efea370e0719839eb91d (patch)
treeac78b9c3824c615c7053fcb6694c38cceafd77a4 /callagent
parent9625d417fe9863ac33146276fbba2ebcf6bef898 (diff)
test: Add test for remote-hangup handling
The whole response handling code was broken. Make sure to increase the test coverage of the system.
Diffstat (limited to 'callagent')
-rw-r--r--callagent/tests/SIPCallAgentTest.st43
1 files changed, 42 insertions, 1 deletions
diff --git a/callagent/tests/SIPCallAgentTest.st b/callagent/tests/SIPCallAgentTest.st
index 4074127..34faeb5 100644
--- a/callagent/tests/SIPCallAgentTest.st
+++ b/callagent/tests/SIPCallAgentTest.st
@@ -21,6 +21,19 @@ TestCase subclass: SIPCallAgentTest [
<category: 'OsmoSIP-Callagent-Tests'>
<comment: 'I will test some basic call agent high-level interaction'>
+ bye: aBranch callId: aCallId toTag: aTag cseq: aCseq [
+ ^(WriteStream on: String new)
+ nextPutAll: 'BYE sip:127.0.0.1 SIP/2.0'; cr; nl;
+ nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
+ nextPutAll: 'Max-Forwards: 70'; cr; nl;
+ nextPutAll: 'CSeq: '; nextPutAll: aCseq displayString; nextPutAll: ' BYE'; cr; nl;
+ nextPutAll: 'Call-Id: '; nextPutAll: aCallId; cr; nl;
+ nextPutAll: 'To: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
+ nextPutAll: 'From: <sip:st@127.0.0.1>;tag=123'; cr; nl;
+ cr; nl;
+ contents
+ ]
+
redirect: aBranch callId: aCallId tag: aTag [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 302 Moved Temporarily'; cr; nl;
@@ -240,7 +253,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: call state equals: #failed.
]
- testWithProxyAuth [
+ setUpProxyAuthCall [
| call msg branch callId fromTag auth secondBranch origCnonce |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
@@ -297,6 +310,12 @@ TestCase subclass: SIPCallAgentTest [
self assert: auth nonceCount equals: '00000002'.
self assert: auth clientNonce equals: origCnonce.
+ ^call
+ ]
+
+ testWithProxyAuth [
+ | call |
+ call := self setUpProxyAuthCall.
"And let it timeout.. With better code and the clientNonce
being stored in the call/initial dialog we could even add
@@ -304,6 +323,28 @@ TestCase subclass: SIPCallAgentTest [
call hangup.
]
+ testWithProxyAuthRemoteBye [
+ | call msg branch callId fromTag sentNr |
+ call := self setUpProxyAuthCall.
+
+ msg := SIPParser parse: sent second data.
+ branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
+ callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
+ fromTag := (msg parameter: 'From' ifAbsent: [nil]).
+
+ sentNr := sent size.
+ self assert: call state equals: SIPCall stateSession.
+
+ transport inject: (self bye: branch callId: callId toTag: fromTag tag cseq: 2).
+ self assert: sent size equals: sentNr + 1.
+ self assert: call state equals: SIPCall stateRemoteHangup.
+
+ msg := SIPParser parse: (sent at: sentNr + 1) data.
+ self assert: msg class equals: SIPResponse.
+ self assert: msg code equals: '200'.
+ self assert: msg phrase equals: 'OK'.
+ ]
+
testInviteWithRedirect [
| call msg branch callId fromTag |