summaryrefslogtreecommitdiffstats
path: root/callagent
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2015-07-24 14:01:19 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2015-07-24 14:01:19 +0200
commitd1e8b2dcd58e32ad509351349314966158e092ca (patch)
tree48e65364b5cb5385015410d7b940d650fab95238 /callagent
parent0d8d65a33066e2aec4133d042679230e719194ce (diff)
cseq: Make the testcases work with different cseq as well
Diffstat (limited to 'callagent')
-rw-r--r--callagent/tests/SIPCallAgentTest.st75
1 files changed, 39 insertions, 36 deletions
diff --git a/callagent/tests/SIPCallAgentTest.st b/callagent/tests/SIPCallAgentTest.st
index 6e56fd4..ff62780 100644
--- a/callagent/tests/SIPCallAgentTest.st
+++ b/callagent/tests/SIPCallAgentTest.st
@@ -34,14 +34,14 @@ TestCase subclass: SIPCallAgentTest [
contents
]
- redirect: aBranch callId: aCallId tag: aTag [
+ redirect: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 302 Moved Temporarily'; cr; nl;
nextPutAll: 'Allow: INVITE, ACK'; cr; nl;
nextPutAll: 'Call-Id: '; nextPutAll: aCallId; cr; nl;
nextPutAll: 'Contact: sip:+12345678@10.8.254.1'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
- nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
+ nextPutAll: 'CSeq: '; nextPutAll: aCseq asString; nextPutAll: ' INVITE'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
nextPutAll: 'From: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
nextPutAll: 'To: <sip:st@127.0.0.1>'; cr; nl;
@@ -51,12 +51,12 @@ TestCase subclass: SIPCallAgentTest [
contents
]
- trying: aBranch callId: aCallId tag: aTag [
+ trying: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 100 Trying'; cr; nl;
nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
- nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
+ nextPutAll: 'CSeq: '; nextPutAll: aCseq asString; nextPutAll: ' INVITE'; cr; nl;
nextPutAll: 'From: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
nextPutAll: 'To: <sip:st@127.0.0.1>'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
@@ -77,7 +77,7 @@ TestCase subclass: SIPCallAgentTest [
contents
]
- invalidAuthorizationRequired: aBranch callId: aCallId tag: aTag [
+ invalidAuthorizationRequired: aBranch callId: aCallId tag: aTag cseq: aCseq [
"This is missing WWW-Authenticate so it is kind of invalid"
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 401 Unauthorized'; cr; nl;
@@ -85,7 +85,7 @@ TestCase subclass: SIPCallAgentTest [
nextPutAll: 'From: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
nextPutAll: 'To: <sip:st@127.0.0.1>'; cr; nl;
nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
- nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
+ nextPutAll: 'CSeq: '; nextPutAll: aCseq asString; nextPutAll: ' INVITE'; cr; nl;
nextPutAll: 'Server: YATE/5.1.0'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
@@ -93,10 +93,6 @@ TestCase subclass: SIPCallAgentTest [
contents
]
- authorizationRequired: aBranch callId: aCallId tag: aTag [
- ^self authorizationRequired: aBranch callId: aCallId tag: aTag cseq: 1
- ]
-
authorizationRequired: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 401 Unauthorized'; cr; nl;
@@ -141,21 +137,22 @@ TestCase subclass: SIPCallAgentTest [
]
testSimpleInvite [
- | call msg |
+ | call msg cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
self assert: call state equals: SIPCall stateInvite.
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
self assert: msg class verb equals: SIPInviteRequest verb.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
call cancel.
self assert: call state equals: SIPCall stateCancel.
]
testInviteWithInvalidAuthorization [
- | call msg branch callId fromTag auth |
+ | call msg branch callId fromTag auth cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
@@ -163,20 +160,21 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
self assert: call state equals: SIPCall stateInvite.
"Now inject an auth requirement message"
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
- transport inject: (self invalidAuthorizationRequired: branch callId: callId tag: fromTag tag).
+ transport inject: (self invalidAuthorizationRequired: branch callId: callId tag: fromTag tag cseq: cseq).
self assert: call state equals: SIPCall stateFailed.
self assert: sent size equals: 1.
]
testInviteWithAuthorization [
- | call msg branch callId fromTag auth secondBranch |
+ | call msg branch callId fromTag auth secondBranch cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
@@ -184,14 +182,15 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
self assert: call state equals: SIPCall stateInvite.
"Now inject an auth requirement message"
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
- transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag).
+ transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag cseq: cseq).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
@@ -202,7 +201,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: cseq + 1.
self assert: call state equals: SIPCall stateInvite.
"Verify the auth part of the message"
@@ -219,7 +218,7 @@ TestCase subclass: SIPCallAgentTest [
]
testInviteWithDoubleAuth [
- | call msg branch callId fromTag auth |
+ | call msg branch callId fromTag auth cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
@@ -227,14 +226,15 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
self assert: call state equals: SIPCall stateInvite.
"Now inject an auth requirement message"
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
- transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag).
+ transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag cseq: cseq).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
@@ -244,7 +244,7 @@ TestCase subclass: SIPCallAgentTest [
msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: cseq + 1.
self assert: call state equals: SIPCall stateInvite.
"Verify the auth part of the message"
@@ -257,12 +257,12 @@ TestCase subclass: SIPCallAgentTest [
self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'.
"Inject another auth.."
- transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag cseq: 2).
+ transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag cseq: cseq + 1).
self assert: call state equals: #failed.
]
setUpProxyAuthCall [
- | call msg branch callId fromTag auth secondBranch origCnonce |
+ | call msg branch callId fromTag auth secondBranch origCnonce cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
@@ -270,14 +270,15 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
self assert: call state equals: SIPCall stateInvite.
"Now inject an auth requirement message"
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
- transport inject: (self proxyAuthRequired: branch callId: callId tag: fromTag tag cseq: 1).
+ transport inject: (self proxyAuthRequired: branch callId: callId tag: fromTag tag cseq: cseq).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
@@ -288,7 +289,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: cseq + 1.
self assert: call state equals: SIPCall stateInvite.
"Verify the auth part of the message"
@@ -307,10 +308,10 @@ TestCase subclass: SIPCallAgentTest [
origCnonce := auth clientNonce.
"Inject a 200 and check the ACK"
- transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: 2).
+ transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: cseq + 1).
self assert: sent size equals: 4.
msg := agent parser parse: (sent at: 4) data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: cseq + 1.
self assert: call state equals: SIPCall stateSession.
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
self deny: auth isNil.
@@ -336,18 +337,19 @@ TestCase subclass: SIPCallAgentTest [
]
testWithProxyAuthRemoteBye [
- | call msg branch callId fromTag sentNr |
+ | call msg branch callId fromTag sentNr cseq |
call := self setUpProxyAuthCall.
msg := agent parser parse: sent second data.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
sentNr := sent size.
self assert: call state equals: SIPCall stateSession.
- transport inject: (self bye: branch callId: callId toTag: fromTag tag cseq: 2).
+ transport inject: (self bye: branch callId: callId toTag: fromTag tag cseq: cseq + 1).
self assert: sent size equals: sentNr + 1.
self assert: call state equals: SIPCall stateRemoteHangup.
@@ -359,7 +361,7 @@ TestCase subclass: SIPCallAgentTest [
]
testInviteWithRedirect [
- | call msg branch callId fromTag |
+ | call msg branch callId fromTag cseq |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
@@ -367,18 +369,19 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
- self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ cseq := (msg parameter: 'CSeq' ifAbsent: [-1]) number.
+ self assert: cseq >= 0.
self assert: call state equals: SIPCall stateInvite.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
"Inject a 100 trying"
- transport inject: (self trying: branch callId: callId tag: fromTag tag).
+ transport inject: (self trying: branch callId: callId tag: fromTag tag cseq: cseq).
self assert: call state equals: SIPCall stateInvite.
"We could inject a 100 Trying but Now inject an auth requirement message"
- transport inject: (self redirect: branch callId: callId tag: fromTag tag).
+ transport inject: (self redirect: branch callId: callId tag: fromTag tag cseq: cseq).
self assert: call state equals: SIPCall stateRedirect.
"Check we get the ACK"