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

invite: Deal with re-transmit of a rejected call

In case our reject does not arrive and is re-transmitted we
should reject it too.

* Modify SIPDialog>>#checkCompatible. We have to accept that
  the remote does not know the tag we assigned. Be more forgiving
* Send the INVITE again and count our rejects.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-27 21:18:49 +02:00
parent b2099a8474
commit 01260bb20e
4 changed files with 37 additions and 8 deletions

View File

@ -211,7 +211,13 @@ Object subclass: SIPDialog [
"I check if the remote and the local dialog match. I do this by cross
checking the to/from, from/to."
self callId = aDialog callId ifFalse: [^false].
self from_tag = aDialog to_tag ifFalse: [^false].
self from_tag = aDialog to_tag ifFalse: [
"In case of a re-transmission of a SIP request the remote does
not have our local tag yet. Deal with it by checking if we have
the remote tag. TODO: maybe look at the kind of request being
made."
(self isClient and: [self to_tag isNil])
ifTrue: [^false]].
self to_tag = aDialog from_tag ifFalse: [^false].
^true

View File

@ -35,6 +35,7 @@ SIPCallBase subclass: SIPIncomingCall [
self stateInvite -> self stateSession.
self stateInvite -> self stateRejected.
self stateInvite -> self stateFailed.
self stateRejected -> self stateRejected.
self stateSession -> self stateHangup.
self stateSession -> self stateRemoteHangup.
}
@ -85,5 +86,13 @@ SIPCallBase subclass: SIPIncomingCall [
expandMacrosWith: dialog cseq with: 'INVITE');
yourself.
ua queueData: resp asDatagram dialog: dialog.
self unregisterDialog.
]
remoteReInvite: aRequest dialog: aDialog [
self state = self class stateRejected
ifTrue: [^self reject].
^self error: ('SIPIncomingCall(<1s>) unknown action for state <2s>'
expandMacrosWith: self callId with: self state) area: #sip.
]
]

View File

@ -75,9 +75,13 @@ a proper session.'>
ua registerDialog: self.
]
unregisterDialogIsPending [
^rem isNil not
]
unregisterDialog [
<category: 'session'>
rem isNil ifTrue: [
rem ifNil: [
rem := Osmo.TimerScheduler instance
scheduleInSeconds: 60 block: [
ua unregisterDialog: self.

View File

@ -73,7 +73,6 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
sent first data printNl.
msg := SIPParser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
@ -81,11 +80,14 @@ TestCase subclass: SIPInviteTest [
]
testRejectCall [
| msg |
| msg call calls firstTag secondTag |
calls := 0.
agent onNewCall: [:invite :dialog |
(SIPIncomingCall initWith: invite dialog: dialog on: agent)
reject].
calls := calls + 1.
call := (SIPIncomingCall initWith: invite dialog: dialog on: agent)
reject; yourself].
"Inject the invite"
transport inject: self createInvite.
@ -93,10 +95,18 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
sent first data printNl.
msg inspect.
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 := SIPParser parse: sent second data.
secondTag := (msg parameter: 'To' ifAbsent: []) tag.
self assert: firstTag equals: secondTag.
]
]