smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

call: Handle CANCEL and verify that the right messages are returned

The code does not verify that sessionFailed is called but it
does verify that the dialogue is scheduled for removal and
that 487/200 is returned.
This commit is contained in:
Holger Hans Peter Freyther 2014-08-29 20:30:20 +02:00
parent 9161371a32
commit 89e653a41a
3 changed files with 91 additions and 6 deletions

View File

@ -47,3 +47,11 @@ SIPACKRequest extend [
aCall sessionAcked: self dialog: aDialog.
]
]
SIPCancelRequest extend [
sipCallDispatch: aCall dialog: aDialog [
<category: '*OsmoSIP-call'>
self logDebug: ('SIPCall(<1s>) got ACK.' expandMacrosWith: aCall callId) area: #sip.
aCall sessionCanceled: self dialog: aDialog.
]
]

View File

@ -133,18 +133,22 @@ receiving an ACK?
self sendResponse: 200 text: 'OK' data: localSDP.
]
sendResponse: aCode text: aText data: aFile [
respondTo: aDialog code: aCode text: aText data: aFile cseq: aCseq[
| resp |
resp := (SIPResponse code: aCode with: aText)
addParameter: 'Via' value: (ua generateVia: branch);
addParameter: 'From' value: dialog generateFrom;
addParameter: 'To' value: dialog generateTo;
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'From' value: aDialog generateFrom;
addParameter: 'To' value: aDialog generateTo;
addParameter: 'Call-ID' value: aDialog callId;
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: dialog cseq with: 'INVITE');
expandMacrosWith: aDialog cseq with: aCseq);
sdp: aFile;
yourself.
ua queueData: resp asDatagram dialog: dialog.
ua queueData: resp asDatagram dialog: aDialog.
]
sendResponse: aCode text: aText data: aFile [
^self respondTo: dialog code: aCode text: aText data: aFile cseq: 'INVITE'
]
remoteReInvite: aRequest dialog: aDialog [
@ -169,4 +173,20 @@ receiving an ACK?
"We have a new session now"
self sessionNew.
]
sessionCanceled: aCancel dialog: aDialog [
(self moveToState: self class stateFailed) ifFalse: [
self logError: ('SIPIncomingCall(<1s>) failed to handle cancel'
expandMacrosWith: self callId) area: #sip.
self respondTo: aDialog code: '200' text: 'OK' data: nil.
^false].
"Tell the user the session has failed. Use the existing
dialogue to say the request was terminated and to reply
to the CANCEL transaction itself."
self sessionFailed.
self sendResponse: 487 text: 'Request Terminated' data: nil.
self unregisterDialog.
self respondTo: aDialog code: '200' text: 'OK' data: nil cseq: 'CANCEL'.
]
]

View File

@ -56,6 +56,19 @@ TestCase subclass: SIPInviteTest [
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
@ -219,4 +232,48 @@ TestCase subclass: SIPInviteTest [
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'.
]
]