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

callagent: Work on call Call Control, setup the call properly...

- Stop the retransmit timer after we checked the From/To
- Add proper state transitions to SIPCall...
- Support not sending an ACK...
This commit is contained in:
Holger Hans Peter Freyther 2011-07-05 14:20:57 +02:00
parent e3960bea3f
commit 12b320f012
2 changed files with 103 additions and 13 deletions

View File

@ -17,7 +17,7 @@
" "
Object subclass: SIPCall [ Object subclass: SIPCall [
| initial_dialog dialog sdp_offer invite state ua next_cseq | | initial_dialog dialog sdp_offer sdp_result invite state ua next_cseq |
<category: 'SIP-Call'> <category: 'SIP-Call'>
<comment: 'I am a high level class to deal with transactions, <comment: 'I am a high level class to deal with transactions,
sessions and calls. Right now I do not support forking proxies and sessions and calls. Right now I do not support forking proxies and
@ -30,6 +30,7 @@ will simply ignore everything but the first dialog.'>
SIPCall class >> stateCancel [ <category: 'states'> ^ #cancel ] SIPCall class >> stateCancel [ <category: 'states'> ^ #cancel ]
SIPCall class >> stateHangup [ <category: 'states'> ^ #hangup ] SIPCall class >> stateHangup [ <category: 'states'> ^ #hangup ]
SIPCall class >> stateRemoteHangup [ <category: 'states'> ^ #remoteHangup ] SIPCall class >> stateRemoteHangup [ <category: 'states'> ^ #remoteHangup ]
SIPCall class >> stateFailed [ <category: 'states'> ^ #failed ]
LegalStates := nil. LegalStates := nil.
@ -91,6 +92,13 @@ will simply ignore everything but the first dialog.'>
createCall: aSDPOffer [ createCall: aSDPOffer [
<category: 'call'> <category: 'call'>
(self moveToState: self class stateInvite) ifFalse: [
self logError: 'Call failed to start.' area: #sip.
^ false
].
sdp_offer := aSDPOffer. sdp_offer := aSDPOffer.
next_cseq := initial_dialog cseq + 1. next_cseq := initial_dialog cseq + 1.
@ -124,23 +132,69 @@ will simply ignore everything but the first dialog.'>
]. ].
] ]
check: aDialog [
<category: 'private'>
"I check if this enters a new confirmed dialog or if this is the
confirmed dialog."
"We have no confirmed dialog, accept it"
^ dialog isNil
ifTrue: [
aDialog isConfirmed ifTrue: [
dialog := aDialog.
self logError: 'SIPCall dialog is confirmed now.' area: #sip.
].
true]
ifFalse: [
"We could fork things here. For multi party call"
dialog to_tag = aDialog to_tag].
]
callTimedOut [ callTimedOut [
<category: 'call-result'> <category: 'call-result'>
self logError: 'Call timed-out.' area: #sip. self logError: 'Call timed-out.' area: #sip.
(self moveToState: self class stateTimeout) ifFalse: [
^ self logError: 'Call failed to move to timeout.' area: #sip.
].
] ]
callSuccess: aResponse dialog: aDialog [ callSuccess: aResponse dialog: aDialog [
<category: 'call-result'> <category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring.' area: #sip.
^ false
].
(self moveToState: self class stateSession) ifTrue: [
self logError: 'Call session etsablished.' area: #sip. self logError: 'Call session etsablished.' area: #sip.
sdp_result := aResponse sdp.
self newSession.
^ true
].
^ false
] ]
callFailure: aResponse dialog: aDialog [ callFailure: aResponse dialog: aDialog [
<category: 'call-result'> <category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
^ false
].
(self moveToState: self class stateFailed) ifTrue: [
self logError: 'Call Failure.' area: #sip. self logError: 'Call Failure.' area: #sip.
self newFailed.
].
] ]
callNotification: aResponse dialog: aDialog [ callNotification: aResponse dialog: aDialog [
<category: 'call-result'> <category: 'call-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring notification.' area: #sip.
^ false
].
self logError: 'Call Notification.' area: #sip. self logError: 'Call Notification.' area: #sip.
] ]
@ -151,18 +205,37 @@ will simply ignore everything but the first dialog.'>
hangupSuccess: aResponse dialog: aDialog [ hangupSuccess: aResponse dialog: aDialog [
<category: 'hangup-result'> <category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
^ false
].
self logError: 'Hang-Up success.' area: #sip. self logError: 'Hang-Up success.' area: #sip.
] ]
hangupFailure: aResponse dialog: aDialog [ hangupFailure: aResponse dialog: aDialog [
<category: 'hangup-result'> <category: 'hangup-result'>
(self check: aDialog) ifFalse: [
self logError: 'Call can only have one session. Ignoring failure.' area: #sip.
^ false
].
self logError: 'Hang-Up failure.' area: #sip. self logError: 'Hang-Up failure.' area: #sip.
] ]
newSession [
<category: 'callback'>
]
newFailed [
<category: 'callback'>
]
nextCSeq [ nextCSeq [
| res | | res |
<category: 'accessing'> <category: 'accessing'>
res := next_cseq. res := next_cseq.
^ (next_cseq := next_cseq + 1) next_cseq := next_cseq + 1.
^ res
] ]
] ]

View File

@ -130,8 +130,9 @@ Object subclass: SIPTransaction [
<category: 'private-dispatch'> <category: 'private-dispatch'>
useragent removeTransaction: self. useragent removeTransaction: self.
success ifNotNil: [ ^ success isNil
success value: aReq value: aDialog] ifTrue: [true]
ifFalse: [success value: aReq value: aDialog].
] ]
respFailure: aReq dialog: aDialog [ respFailure: aReq dialog: aDialog [
@ -143,18 +144,31 @@ Object subclass: SIPTransaction [
] ]
newData: aReq [ newData: aReq [
| code dialog | | code dialog new_cseq |
<category: 'private-dispatch'> <category: 'private-dispatch'>
('Found response %1 %2' % {aReq code. aReq phrase}) printNl. ('Found response %1 %2' % {aReq code. aReq phrase}) printNl.
sem critical: [ "Compare the sequence number"
retransmit_time cancel. new_cseq := (aReq parameter: 'CSeq' ifAbsent: [
fail_time cancel. self logError: '%1(%2) response lacks CSeq.'
% {self class. self branch} area: #sip.
^ false
]) number.
cseq = new_cseq ifFalse: [
self logError: '%1(%2) wrong cseq:. %1 %2.'
% {self class. self branch. cseq. new_cseq} area: #sip.
^ false
]. ].
"Store all dialogs.... and match them..." "Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aReq. dialog := initial_dialog newFromRequest: aReq.
sem critical: [
retransmit_time cancel.
fail_time cancel.
].
code := aReq code asInteger. code := aReq code asInteger.
code < 200 ifTrue: [ code < 200 ifTrue: [
^ self respNotification: aReq dialog: dialog ^ self respNotification: aReq dialog: dialog
@ -285,9 +299,12 @@ SIPTransaction subclass: SIPInviteTransaction [
| branch | | branch |
branch := useragent class generateBranch. branch := useragent class generateBranch.
self changeState: self class stateTerminated. 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 self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog. dialog: aDialog.
^ super respSuccess: aReq dialog: aDialog. ]
] ]
respFailure: aReq dialog: aDialog [ respFailure: aReq dialog: aDialog [