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

callagent: Introduce the SIPSessionBase, prepare handling Requests

The name session base is a bit misleading as it is not the session
that holds the initial dialog, the confirmed dialog, the UAS and then
also the session when it is setup. When the dialog gets confirmed we
will register it with the useragent and then will be called for new
requests. On hangup/cancel the dialog will be scheduled for removal.
This commit is contained in:
Holger Hans Peter Freyther 2011-07-06 19:26:37 +02:00
parent 44efac4f5b
commit 93f816ea4f
3 changed files with 136 additions and 48 deletions

View File

@ -16,9 +16,95 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPCall [
| initial_dialog dialog sdp_offer sdp_result invite state ua next_cseq |
<category: 'SIP-Call'>
PackageLoader fileInPackage: 'OsmoCore'.
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
<category: 'SIP-Session'>
<comment: 'I am the base for sessions. I am a bit backward as the
Dialog will create/hold the session but we start with the session here
as this is what we are really interested in. So this is not really a
session as of the RFC... but at some stage in the exchange we will be
a proper session.'>
SIPSessionBase class >> on: aDialog useragent: aUseragent [
<category: 'creation'>
^ self new
useragent: aUseragent;
initialDialog: aDialog;
yourself
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog.
initial_dialog contact: 'sip:osmo_st_sip@%1:%2'
% {ua transport address. ua transport port}.
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
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 registerDialog.
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].
]
registerDialog [
<category: 'session'>
ua registerDialog: self.
]
unregisterDialog [
<category: 'session'>
rem isNil ifTrue: [
rem := Osmo.TimerScheduler instance
scheduleInSeconds: 60 block: [
ua unregisterDialog: self.
]]
]
nextCSeq [
| res |
<category: 'accessing'>
res := next_cseq.
next_cseq := next_cseq + 1.
^ res
]
isCompatible: aDialog [
<category: 'dialog'>
^ dialog isNil
ifTrue: [initial_dialog isCompatible: aDialog]
ifFalse: [dialog isCompatible: aDialog].
]
newRequest: aRequest [
<category: 'dialog'>
'NEW REQUEST' printNl.
]
]
SIPSessionBase subclass: SIPCall [
| sdp_offer sdp_result invite state |
<category: 'SIP-Session'>
<comment: 'I am a high level class to deal with transactions,
sessions and calls. Right now I do not support forking proxies and
will simply ignore everything but the first dialog.'>
@ -51,11 +137,9 @@ will simply ignore everything but the first dialog.'>
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
<category: 'creation'>
^ self new
useragent: aUseragent;
initialDialog: ((SIPDialog fromUser: aUser host: aHost port: aPort)
to: aTo; yourself);
yourself
^ self
on: ((SIPDialog fromUser: aUser host: aHost port: aPort)
to: aTo; yourself) useragent: aUseragent
]
state [
@ -80,18 +164,6 @@ will simply ignore everything but the first dialog.'>
^ true
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog.
initial_dialog contact: 'sip:osmo_st_sip@%1:%2'
% {ua transport address. ua transport port}.
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
createCall: aSDPOffer [
<category: 'call'>
@ -116,6 +188,7 @@ will simply ignore everything but the first dialog.'>
cancel [
<category: 'call'>
(self moveToState: self class stateCancel) ifTrue: [
self unregisterDialog.
invite cancel.
^ true
].
@ -126,6 +199,7 @@ will simply ignore everything but the first dialog.'>
hangup [
<category: 'call'>
(self moveToState: self class stateHangup) ifTrue: [
self unregisterDialog.
(SIPByeTransaction createWith: dialog on: ua cseq: self nextCSeq)
onTimeout: [self hangupTimedOut];
onSuccess: [:resp :dlg | self hangupSuccess: resp dialog: dlg];
@ -134,29 +208,12 @@ 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 [
<category: 'call-result'>
self logError: 'SIPCall timed-out.' area: #sip.
(self moveToState: self class stateTimeout) ifFalse: [
invite := nil.
^ self logError: 'SIPCall failed to move to timeout.' area: #sip.
].
]
@ -173,6 +230,7 @@ will simply ignore everything but the first dialog.'>
self logError: 'SIPCall session etsablished.' area: #sip.
sdp_result := aResponse sdp.
self newSession.
invite := nil.
^ true
].
^ false
@ -186,6 +244,7 @@ will simply ignore everything but the first dialog.'>
].
(self moveToState: self class stateFailed) ifTrue: [
invite := nil.
self logError: 'SIPCall Failure.' area: #sip.
self newFailed.
].
@ -240,12 +299,4 @@ will simply ignore everything but the first dialog.'>
newFailed [
<category: 'callback'>
]
nextCSeq [
| res |
<category: 'accessing'>
res := next_cseq.
next_cseq := next_cseq + 1.
^ res
]
]

View File

@ -224,6 +224,25 @@ SIPUserAgentBase subclass: SIPUserAgent [
sem := Semaphore forMutualExclusion.
]
dialogs [
<category: 'private'>
^ dialogs ifNil: [dialogs := OrderedCollection new]
]
registerDialog: aDialog [
<category: 'dialogs'>
sem critical: [
self dialogs add: aDialog]
]
unregisterDialog: aDialog [
<category: 'dialogs'>
sem critical: [
self dialogs remove: aDialog ifAbsent: [
self logError: '%1 dialog %2 is not present.'
% {self. aDialog} area: #sip]]
]
transactions [
<category: 'private'>
^ transactions ifNil: [transactions := OrderedCollection new]
@ -244,9 +263,16 @@ SIPUserAgentBase subclass: SIPUserAgent [
]
dispatchRequest: aReq [
| dialogs dialog |
<category: 'dispatch'>
self logError: 'Requests are not implemented yet' area: #sip.
self notYetImplemented.
dialog := SIPDialog fromMessage: aReq.
dialogs := sem critical: [self dialogs copy].
dialogs do: [:each |
(each isCompatible: dialog) ifTrue: [
each newRequest: aReq.
^ self
]]
]
dispatchResponse: aReq [

View File

@ -161,6 +161,17 @@ Object subclass: SIPDialog [
^ dest_port
]
isCompatible: aDialog [
<category: 'check'>
"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 to_tag = aDialog from_tag ifFalse: [^false].
^true
]
checkCompatible: other [
<category: 'private'>
"I am checking if the dialog is compatible."