summaryrefslogtreecommitdiffstats
path: root/callagent/tests/SIPCallAgentTest.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-02-14 18:45:47 +0100
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-02-14 18:50:03 +0100
commit9ea9eafc2a29183596e358ab037cddbeecb28c30 (patch)
tree5b8b737c572f0423a0c6e74c1286f2fd02e8e3b9 /callagent/tests/SIPCallAgentTest.st
parent7294d8add0521119225e89070d2c5e5e1e3b6844 (diff)
auth: Implement handling 401 and re-sending the message with auth
This should work for all transactions carried out by the transaction layer but the unit test is only created for INVITE. It has not been verified against another SIP engine yet. It has not been verified for BYE/ACK. Specially for ACK the code might still be wrong as the wrong operation name is taken into account for the digest.
Diffstat (limited to 'callagent/tests/SIPCallAgentTest.st')
-rw-r--r--callagent/tests/SIPCallAgentTest.st103
1 files changed, 100 insertions, 3 deletions
diff --git a/callagent/tests/SIPCallAgentTest.st b/callagent/tests/SIPCallAgentTest.st
index 14e437b..9693251 100644
--- a/callagent/tests/SIPCallAgentTest.st
+++ b/callagent/tests/SIPCallAgentTest.st
@@ -17,17 +17,56 @@
"
TestCase subclass: SIPCallAgentTest [
+ | transport sent agent |
<category: 'OsmoSIP-Callagent-Tests'>
<comment: 'I will test some basic call agent high-level interaction'>
- testSimpleInvite [
- | transport agent call sent msg |
+ invalidAuthorizationRequired: aBranch callId: aCallId tag: aTag [
+ "This is missing WWW-Authenticate so it is kind of invalid"
+ ^(WriteStream on: String new)
+ nextPutAll: 'SIP/2.0 401 Unauthorized'; 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;
+ nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
+ nextPutAll: 'CSeq: 1 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;
+ cr; nl;
+ contents
+ ]
+
+ authorizationRequired: aBranch callId: aCallId tag: aTag [
+ ^(WriteStream on: String new)
+ nextPutAll: 'SIP/2.0 401 Unauthorized'; 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;
+ nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
+ nextPutAll: 'CSeq: 1 INVITE'; cr; nl;
+ nextPutAll: 'WWW-Authenticate: Digest realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", stale=TRUE, algorithm=MD5'; 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;
+ cr; nl;
+ contents
+ ]
+
+ setUp [
sent := OrderedCollection new.
transport := SIPTransportMock new
onData: [:datagram | sent add: datagram];
yourself.
agent := SIPUserAgent createOn: transport.
- call := SIPCall fromUser: 'test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
+ agent
+ username: 'st';
+ password: 'st'.
+ ]
+
+ testSimpleInvite [
+ | call msg |
+ call := SIPCall fromUser: '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.
@@ -38,4 +77,62 @@ TestCase subclass: SIPCallAgentTest [
call cancel.
self assert: call state equals: SIPCall stateCancel.
]
+
+ testInviteWithInvalidAuthorization [
+ | call msg branch callId fromTag auth |
+
+ 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'.
+
+ "First assertions for the invite"
+ self assert: sent size equals: 1.
+ msg := SIPParser parse: sent first data.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ 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).
+ self assert: call state equals: SIPCall stateFailed.
+ self assert: sent size equals: 1.
+ ]
+
+ testInviteWithAuthorization [
+ | call msg branch callId fromTag auth |
+
+ 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'.
+
+ "First assertions for the invite"
+ self assert: sent size equals: 1.
+ msg := SIPParser parse: sent first data.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ 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).
+
+ "Verify that a second message has been sent and it contains an auth result"
+ self assert: sent size equals: 2.
+ msg := SIPParser parse: sent second data.
+ self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
+ self assert: call state equals: SIPCall stateInvite.
+
+ "Verify the auth part of the message"
+ auth := msg parameter: 'Authorization' ifAbsent: [nil].
+ self deny: auth isNil.
+ self assert: auth username equals: 'st'.
+ self assert: auth realm equals: 'Yate'.
+ self assert: auth uri equals: 'sip:127.0.0.1'.
+ self assert: auth nonce equals: '373ef30b297545cbce99fad09f1409cb.1392124197'.
+ self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'.
+
+ call cancel.
+ self assert: call state equals: SIPCall stateCancel.
+ ]
]