smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/callagent/tests/SIPCallAgentTest.st

389 lines
18 KiB
Smalltalk

"
(C) 2014 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 <http://www.gnu.org/licenses/>.
"
TestCase subclass: SIPCallAgentTest [
| transport sent agent |
<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;
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: '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: 'Max-Forwards: 70'; cr; nl;
nextPutAll: 'Supported: replaces'; cr; nl;
cr; nl;
contents
]
trying: aBranch callId: aCallId tag: aTag [
^(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: '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;
cr; nl;
contents
]
ok: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 200 OK'; cr; nl;
nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
nextPutAll: 'CSeq: '; nextPutAll: aCseq displayString; 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>;tag=123'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
cr; nl;
contents
]
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 [
^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;
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: '; nextPutAll: aCseq displayString; nextPutAll: ' 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
]
proxyAuthRequired: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 407 Proxy Authentication Required'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
nextPutAll: 'Proxy-Authenticate: Digest realm="07440491",qop="auth",nonce="06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8",algorithm=MD5'; 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: '; nextPutAll: aCseq displayString; 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;
cr; nl;
contents
]
setUp [
sent := OrderedCollection new.
transport := SIPTransportMock new
onData: [:datagram | sent add: datagram];
yourself.
agent := SIPUserAgent createOn: transport.
agent
username: 'st';
password: 'st'.
]
testSimpleInvite [
| call msg |
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.
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 := agent parser 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 secondBranch |
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 := agent parser 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: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
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: 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.
]
testInviteWithDoubleAuth [
| 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 := agent parser 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: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
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: 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'.
"Inject another auth.."
transport inject: (self authorizationRequired: branch callId: callId tag: fromTag tag cseq: 2).
self assert: call state equals: #failed.
]
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.
call createCall: 'dummy-sdp'.
"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.
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).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
msg := agent parser parse: sent third data.
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: call state equals: SIPCall stateInvite.
"Verify the auth part of the message"
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
self deny: auth isNil.
self assert: auth username equals: 'st'.
self assert: auth realm equals: '07440491'.
self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth nonce equals: '06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8'.
self assert: auth qop equals: 'auth'.
self assert: auth nonceCount equals: '00000001'.
"Fields that depend on the random clientNonce"
self assert: auth response size equals: 32.
self assert: auth clientNonce size equals: 8.
origCnonce := auth clientNonce.
"Inject a 200 and check the ACK"
transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: 2).
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: call state equals: SIPCall stateSession.
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
self deny: auth isNil.
self assert: auth username equals: 'st'.
self assert: auth realm equals: '07440491'.
self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth nonce equals: '06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8'.
self assert: auth qop equals: 'auth'.
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
the Proxy-Authorization to the BYE message.."
call hangup.
]
testWithProxyAuthRemoteBye [
| call msg branch callId fromTag sentNr |
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]).
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 := agent parser parse: (sent at: sentNr + 1) data.
self assert: msg class equals: SIPResponse.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: (msg parameter: 'From' ifAbsent: [nil]) tag equals: '123'.
]
testInviteWithRedirect [
| call msg branch callId fromTag |
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 := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
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).
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).
self assert: call state equals: SIPCall stateRedirect.
"Check we get the ACK"
msg := agent parser parse: sent second data.
self assert: msg class equals: SIPACKRequest.
]
]