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

callagent: Check if two SIPDialog's are compatible

This commit is contained in:
Holger Hans Peter Freyther 2011-07-05 12:06:36 +02:00
parent 6bc4e9826d
commit e3960bea3f
3 changed files with 54 additions and 13 deletions

View File

@ -83,7 +83,13 @@ Object subclass: SIPDialog [
to_tag := aTag
]
callId: aCallId [
<category: 'private'>
call_id := aCallId
]
callId [
<category: 'accessing'>
^ call_id
]
@ -155,27 +161,45 @@ Object subclass: SIPDialog [
^ dest_port
]
checkCompatible: other [
<category: 'private'>
"I am checking if the dialog is compatible."
self callId = other callId ifFalse: [
^ self error: 'SIPDialog is not compatible due wrong CallID %1 %2.'
% {self callId. other callId}.
].
self from_tag = other from_tag ifFalse: [
^ self error: 'SIPDialog is not compatible due wrong from tag %1 %2.'
% {self from_tag. other from_tag}
].
self to_tag isNil ifFalse: [
self to_tag = other to_tag ifFalse: [
^ self error: 'SIPDialog is not compatible due to tag %1 %2.'
% {self to_tag. other to_tag}
].
].
]
newFromRequest: aReq [
| to pos tag|
| to other |
<category: 'handling'>
"I try to confirm a dialog"
"I try to confirm a dialog, i also verify that it is somehow compatible."
other := SIPDialog fromMessage: aReq.
self checkCompatible: other.
"I am already confirmed."
self isConfirmed ifTrue: [^self].
"I have a tag but I am not confirmed, create a copy and confirm"
to_tag ifNotNil: [
^ self copy
confirm;
yourself].
"There is no To... hmm return us"
to := aReq parameter: 'To' ifAbsent: [^self].
(tag := to tag) isNil ifTrue: [
^ self].
to tag isNil ifTrue: [^self].
^ self copy
toTag: tag;
toTag: to tag;
confirm;
yourself.
]

View File

@ -74,4 +74,23 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
assert: dialog callId = 'MzY3NzE3ODgyNw__@xiaoyu';
assert: dialog cseq = 1.
]
testDialogCompatible [
| initial_dialog dialog1 dialog2 |
initial_dialog := (SIPDialog
fromUser: 'sip:1000@on-waves.com' host: '0.0.0.0' port: 5060)
fromTag: 'MzQ4NTQ0MTg2NzIyNDEwNjkyNjY_';
callId: 'MzY3NzE3ODgyNw__@xiaoyu';
yourself.
self assert: initial_dialog isUnconfirmed.
self deny: initial_dialog isConfirmed.
dialog1 := initial_dialog newFromRequest: (self parse: self testResponseData).
self deny: initial_dialog == dialog1.
self assert: dialog1 isConfirmed.
dialog2 := dialog1 newFromRequest: (self parse: self testResponseData).
self assert: dialog1 == dialog2.
self assert: dialog2 isConfirmed.
]
]

View File

@ -152,8 +152,6 @@ Object subclass: SIPTransaction [
fail_time cancel.
].
"Verify the To/From tags here"
"Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aReq.