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

callagent: Work on canceling a transaction..

This is still more complicated (and wrong) then it should be,
when we CANCEL an INVITE we can either send a CANCEL or we need
to wait for a 100. Now the CANCEL could be too late (the server
already sent a 200), in that case we would get a 200 for the
INVITE and pass this to the higher levels (which we probably
should).
This commit is contained in:
Holger Hans Peter Freyther 2011-07-05 20:27:22 +02:00
parent 9aa3efa1f4
commit f997ab4fbc
2 changed files with 141 additions and 32 deletions

View File

@ -71,7 +71,8 @@ will simply ignore everything but the first dialog.'>
"Check if there is a state transition"
(self class legalStates includes: (self state -> aState)) ifFalse: [
self logError: 'State transition %1->%2 is not legal' % {self state. aState} area: #sip.
self logError: 'SIPCall transition %1->%2 is not legal.'
% {self state. aState} area: #sip.
^ false
].
@ -95,7 +96,7 @@ will simply ignore everything but the first dialog.'>
<category: 'call'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: 'Call failed to start.' area: #sip.
self logError: 'SIPCall failed to start.' area: #sip.
^ false
].
@ -153,22 +154,23 @@ will simply ignore everything but the first dialog.'>
callTimedOut [
<category: 'call-result'>
self logError: 'Call timed-out.' area: #sip.
self logError: 'SIPCall timed-out.' area: #sip.
(self moveToState: self class stateTimeout) ifFalse: [
^ self logError: 'Call failed to move to timeout.' area: #sip.
^ self logError: 'SIPCall failed to move to timeout.' area: #sip.
].
]
callSuccess: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring.' area: #sip.
self logError: 'SIPCall can only have one session. Ignoring.' area: #sip.
^ false
].
(self moveToState: self class stateSession) ifTrue: [
self logError: 'Call session etsablished.' area: #sip.
self logError: 'SIPCall session etsablished.' area: #sip.
sdp_result := aResponse sdp.
self newSession.
^ true
@ -179,12 +181,12 @@ will simply ignore everything but the first dialog.'>
callFailure: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
self logError: 'SIPCall can only have one session. Ignoring failure.' area: #sip.
^ false
].
(self moveToState: self class stateFailed) ifTrue: [
self logError: 'Call Failure.' area: #sip.
self logError: 'SIPCall Failure.' area: #sip.
self newFailed.
].
]
@ -192,11 +194,11 @@ will simply ignore everything but the first dialog.'>
callNotification: aResponse dialog: aDialog [
<category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring notification.' area: #sip.
self logError: 'SIPCall can only have one session. Ignoring notification.' area: #sip.
^ false
].
self logError: 'Call Notification.' area: #sip.
self logError: 'SIPCall Notification.' area: #sip.
]
hangupTimedOut [
@ -207,7 +209,7 @@ will simply ignore everything but the first dialog.'>
hangupSuccess: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
self logError: 'SIPCall can only have one session. Ignoring failure.' area: #sip.
^ false
].
@ -217,7 +219,7 @@ will simply ignore everything but the first dialog.'>
hangupFailure: aResponse dialog: aDialog [
<category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
self logError: 'SIPCall can only have one session. Ignoring failure.' area: #sip.
^ false
].

View File

@ -29,6 +29,7 @@ Object subclass: SIPTransaction [
SIPTransaction class >> stateProceeding [ <category: 'states'> ^ #proceeding ]
SIPTransaction class >> stateCompleted [ <category: 'states'> ^ #completed ]
SIPTransaction class >> stateTerminated [ <category: 'states'> ^ #terminated ]
SIPTransaction class >> stateCanceled [ <category: 'states'> ^ #canceled ]
SIPTransaction class >> createWith: aDialog on: aUA cseq: aCseq [
<category: 'creation'>
@ -143,12 +144,10 @@ Object subclass: SIPTransaction [
failure value: aReq value: aDialog]
]
newData: aReq [
| code dialog new_cseq |
checkSequenceNumber: aReq [
| new_cseq |
<category: 'private-dispatch'>
('Found response %1 %2' % {aReq code. aReq phrase}) printNl.
"Compare the sequence number"
"I have to verify the sequence numbers..."
new_cseq := (aReq parameter: 'CSeq' ifAbsent: [
self logError: '%1(%2) response lacks CSeq.'
% {self class. self branch} area: #sip.
@ -161,25 +160,50 @@ Object subclass: SIPTransaction [
^ false
].
"Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aReq.
^ true
]
stopRetransmitTimer [
<category: 'private'>
"I stop the retransmit timers, e.g. because there was a request,
or there was a timeout, or someone canceled things."
sem critical: [
retransmit_time cancel.
fail_time cancel.
].
]
]
code := aReq code asInteger.
newData: aResp [
| dialog |
<category: 'private-dispatch'>
('Found response %1 %2' % {aResp code. aResp phrase}) printNl.
(self checkSequenceNumber: aResp) ifFalse: [^ false].
"Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aResp.
self stopRetransmitTimer.
self dispatchDialog: dialog response: aResp.
]
dispatchDialog: dialog response: aResp [
| code |
<category: 'private-dispatch'>
code := aResp code asInteger.
code < 200 ifTrue: [
^ self respNotification: aReq dialog: dialog
^ self respNotification: aResp dialog: dialog
].
code = 200 ifTrue: [
^ self respSuccess: aReq dialog: dialog
^ self respSuccess: aResp dialog: dialog
].
code > 200 ifTrue: [
^ self respFailure: aReq dialog: dialog
^ self respFailure: aResp dialog: dialog
]
]
@ -251,14 +275,14 @@ Object subclass: SIPTransaction [
^ ack
]
createBye [
createBye: aDialog [
| bye |
<category: 'invite'>
bye := (SIPByeRequest from: initial_dialog)
bye := (SIPByeRequest from: aDialog)
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'BYE'};
addParameter: 'Call-ID' value: initial_dialog callId;
addParameter: 'Call-ID' value: aDialog callId;
yourself.
useragent injectDefaults: bye.
^ bye
@ -304,24 +328,107 @@ SIPTransaction subclass: SIPInviteTransaction [
self queueData: invite asDatagram dialog: initial_dialog.
]
dispatchDialog: aDialog response: aResponse [
| cseq |
<category: 'private-dispatch'>
"The INVITE transaction is a bit more complicated. It is the only
transaction that can be canceled and we will need to do some things
to check if this is canceled. We have some indirections here
1.) we get a 200 for a BYE/CANCEL in the CSeq
2.) we get a reply but we should cancel, e.g. we were waiting for
a proceeding/notification or the call is too far in the setup
and we will just bye it.
3.) the normal dispatch..."
cseq := aResponse parameter: 'CSeq' ifAbsent: [].
cseq method = 'INVITE'
ifTrue: [self dispatchInvite: aDialog response: aResponse]
ifFalse: [self dispatchOther: aDialog response: aResponse].
]
dispatchOther: aDialog response: aResponse [
| cseq code |
<category: 'private-dispatch'>
code := aResponse code asInteger.
cseq := aResponse parameter: 'CSeq' ifAbsent: [].
code = 200 ifTrue: [
self removeTransaction.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
].
]
handleCancel: aDialog response: aResponse [
| code |
<category: 'private-dispatch'>
code := aResponse code asInteger.
"We will send a CANCEL, maybe it is already the second."
code < 200 ifTrue: [
self queueData: (self createCancel asDatagram) dialog: initial_dialog.
].
"We are connected but we didn't want to, let us BYE it"
(code = 200 or: [(code > 200 and: [code ~= 487])]) ifTrue: [
| bye branch |
branch := useragent class generateBranch.
self removeTransaction.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
bye := SIPByeTransaction
createWith: aDialog on: useragent cseq: cseq + 1.
bye start.
].
]
dispatchInvite: aDialog response: aResponse [
<category: 'private-dispatch'>
"Send a cancel if this is a non final response"
canceled
ifTrue: [self handleCancel: aDialog response: aResponse]
ifFalse: [super dispatchDialog: aDialog response: aResponse].
]
respSuccess: aReq dialog: aDialog [
| branch |
<category: 'private-dispatch'>
branch := useragent class generateBranch.
self changeState: self class stateTerminated.
"TODO: We probably want to accept and then release/BYE it"
(super respSuccess: aReq dialog: aDialog) ifTrue: [
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
"We send the ACK, if our callbacks don't like the result we
will need to send a BYE to stop that session."
self queueData: (self createAck: branch dialog: aDialog) asDatagram dialog: aDialog.
(super respSuccess: aReq dialog: aDialog) ifFalse: [| bye |
bye := SIPByeTransaction
createWith: aDialog on: useragent cseq: cseq + 1.
bye start.
]
]
respFailure: aReq dialog: aDialog [
<category: 'private-dispatch'>
self changeState: self class stateCompleted.
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
^ super respFailure: aReq dialog: aDialog.
]
cancel [
<category: 'cancel'>
canceled := true.
self stopRetransmitTimer.
self changeState: self class stateCanceled.
self state = self class stateProceeding ifTrue: [
self queueData: self createCancel asDatagram dialog: initial_dialog.
].
self state = self class stateCompleted ifTrue: [
self logError: 'SIPTransaction already completed.' area: #sip.
].
]
]
SIPTransaction subclass: SIPByeTransaction [
@ -329,7 +436,7 @@ SIPTransaction subclass: SIPByeTransaction [
transmit [
| bye |
bye := self createBye.
bye := self createBye: initial_dialog.
self queueData: bye asDatagram dialog: initial_dialog.
]
]