smalltalk
/
osmo-st-all
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-all/callagent/tests/SIPInviteTest.st

280 lines
10 KiB
Smalltalk

"
(C) 2011,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: SIPInviteTest [
| sent transport agent dialog |
<category: 'OsmoSIP-Callagent-Tests'>
<comment: 'Test incoming SIP INVITES. This should create a
new dialog/transaction and a SIPCall based on that. The call
can be accepted or rejected.'>
createInvite [
^(WriteStream on: String new)
nextPutAll: 'INVITE sip:+99915123456@10.23.43.2 SIP/2.0'; cr; nl;
nextPutAll: 'Max-Forwards: 19'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 10.23.43.1:5060;rport;branch=z9hG4bK1675813621'; cr; nl;
nextPutAll: 'From: "00331234567" <sip:00331234567@10.23.43.1>;tag=807191241'; cr; nl;
nextPutAll: 'To: <sip:+99915123456@10.23.43.2>'; cr; nl;
nextPutAll: 'Call-ID: 726660594@10.23.43.1'; cr; nl;
nextPutAll: 'CSeq: 3 INVITE'; cr; nl;
nextPutAll: 'User-Agent: BLOAT/4.3.0'; cr; nl;
nextPutAll: 'Contact: <sip:00331234567@10.23.43.1:5060>'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
nextPutAll: 'Content-Type: application/sdp'; cr; nl;
nextPutAll: 'Content-Length: 189'; cr; nl;
cr; nl;
nextPutAll: 'Shiny remote SDP file'; cr; nl;
cr; nl;
contents
]
createAck: aTag [
^(WriteStream on: String new)
nextPutAll: 'ACK sip:127.0.0.1 SIP/2.0'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 10.23.43.1:5060;rport;branch=z9hG4bK1675813621'; cr; nl;
nextPutAll: 'CSeq: 3 ACK'; cr; nl;
nextPutAll: 'Call-ID: 726660594@10.23.43.1'; cr; nl;
nextPutAll: 'From: "00331234567" <sip:00331234567@10.23.43.1>;tag=807191241'; cr; nl;
nextPutAll: 'To: <sip:+99915123456@10.23.43.2>;tag='; nextPutAll: aTag; cr; nl;
cr;nl;
contents
]
createCancel [
"Without the tag..."
^String streamContents: [:stream |
stream
nextPutAll: 'CANCEL sip:+99915123456@10.23.43.2 SIP/2.0'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 10.23.43.1:5060;rport;branch=z9hG4bK1675813621'; cr; nl;
nextPutAll: 'CSeq: 5 CANCEL'; cr; nl;
nextPutAll: 'Call-ID: 726660594@10.23.43.1'; cr; nl;
nextPutAll: 'From: "00331234567" <sip:00331234567@10.23.43.1>;tag=807191241'; cr; nl;
nextPutAll: 'To: <sip:+99915123456@10.23.43.2>'; cr; nl;
cr;nl]
]
setUp [
sent := OrderedCollection new.
transport := SIPTransportMock new
onData: [:datagram | sent add: datagram];
yourself.
agent := SIPUserAgent createOn: transport.
agent
username: 'st';
password: 'st'.
dialog := SIPDialog fromUser: 'sip:st@127.0.0.1' host: '127.0.0.1' port: 5060.
dialog identity: agent mainIdentity.
]
testRejectCallDefault [
| msg |
"Inject the invite"
transport inject: self createInvite.
"Check the reject"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs isEmpty.
]
testRejectCall [
| msg call calls firstTag secondTag |
calls := 0.
agent onNewCall: [:invite :dialog |
calls := calls + 1.
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
reject; yourself].
"Inject the invite"
transport inject: self createInvite.
"Check the reject"
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs size equals: 1.
self assert: call unregisterDialogIsPending.
firstTag := (msg parameter: 'To' ifAbsent: []) tag.
"Do a re-transmit and see what happens.."
transport inject: self createInvite.
self assert: call unregisterDialogIsPending.
self assert: sent size equals: 2.
msg := agent parser parse: sent second data.
secondTag := (msg parameter: 'To' ifAbsent: []) tag.
self assert: firstTag equals: secondTag.
]
testConnectedCall [
| msg call tag |
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 messages"
self assert: sent size equals: 3.
msg := agent parser 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.
tag := (msg parameter: 'To' ifAbsent: []) tag.
msg := agent parser 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 := agent parser parse: sent third data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
self assert: (msg parameter: 'Content-Type' ifAbsent: []) equals: 'application/sdp'.
self assert: (msg parameter: 'Content-Length' ifAbsent: []) equals: '10'.
"Inject the ACK for the 200"
self assert: call state equals: call class stateAccepted.
transport inject: (self createAck: tag).
self assert: call state equals: call class stateSession.
self assert: (call remoteSDP startsWith: 'Shiny remote SDP file').
"Now hangup the call"
call hangup.
self assert: call state equals: call class stateHangup.
msg := agent parser parse: sent fourth data.
self assert: msg class equals: SIPByeRequest.
]
testConnectedCallWithRetransmission [
| msg call tag |
agent onNewCall: [:invite :dialog |
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)].
"Inject the invite"
transport inject: self createInvite.
"Check the reject"
self assert: sent size equals: 0.
"Send a 100 Trying to the other end"
call trying.
self assert: sent size equals: 1.
msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
"Retransmit the INVITE to forc another trying"
transport inject: self createInvite.
self assert: sent size equals: 2.
msg := agent parser parse: sent second data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
"Now ring and re-transmit"
call ringing.
self assert: sent size equals: 3.
msg := agent parser parse: sent third data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
transport inject: self createInvite.
self assert: sent size equals: 4.
msg := agent parser parse: (sent at: 4) data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
"Now pick-up..."
call pickUp: 'file'.
self assert: sent size equals: 5.
msg := agent parser parse: (sent at: 5) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
transport inject: self createInvite.
self assert: sent size equals: 6.
msg := agent parser parse: (sent at: 6) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
]
testCanceledCall [
| msg call tag |
agent onNewCall: [:invite :dialog |
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
trying;
yourself].
"Inject the invite"
transport inject: self createInvite.
"Check the messages"
self assert: sent size equals: 1.
msg := agent parser 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.
tag := (msg parameter: 'To' ifAbsent: []) tag.
"Now cancel and see what is happening!"
transport inject: self createCancel.
"We expect a 487 and a 200. The 487 needs to be for the old
and existign dialog."
self assert: sent size equals: 3.
self assert: agent dialogs size equals: 1.
self assert: agent dialogs first unregisterDialogIsPending.
msg := agent parser parse: sent second data.
self assert: msg code equals: '487'.
self assert: msg phrase equals: 'Request Terminated'.
self assert: (msg parameter: 'To' ifAbsent: []) tag equals: tag.
self assert: (msg parameter: 'CSeq' ifAbsent: []) number equals: 3.
self assert: (msg parameter: 'CSeq' ifAbsent: []) method equals: 'INVITE'.
msg := agent parser parse: sent third data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: (msg parameter: 'To' ifAbsent: []) tag isNil.
self assert: (msg parameter: 'CSeq' ifAbsent: []) number equals: 5.
self assert: (msg parameter: 'CSeq' ifAbsent: []) method equals: 'CANCEL'.
]
]