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

misc: Split SIPCall.st into separate files

This commit is contained in:
Holger Hans Peter Freyther 2014-02-15 18:02:53 +01:00
parent 2454ca1372
commit 1e4cb83af0
4 changed files with 146 additions and 110 deletions

View File

@ -0,0 +1,33 @@
"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
SIPRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logError: ('SIPCall(<1s>) got unhandled request <2p>.'
expandMacrosWithArguments: {aCall callId. self class verb}) area: #sip.
]
]
SIPByeRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logDebug: ('SIPCall(<1s>) got BYE.' expandMacrosWith: aCall callId) area: #sip.
aCall remoteHangup: self.
]
]

View File

@ -16,115 +16,6 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
SIPRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logError: ('SIPCall(<1s>) got unhandled request <2p>.'
expandMacrosWithArguments: {aCall callId. self class verb}) area: #sip.
]
]
SIPByeRequest extend [
sipCallDispatch: aCall [
<category: '*OsmoSIP-call'>
self logDebug: ('SIPCall(<1s>) got BYE.' expandMacrosWith: aCall callId) area: #sip.
aCall remoteHangup: self.
]
]
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
<category: 'OsmoSIP-Callagent'>
<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@<1p>:<2p>'
expandMacrosWith: ua transport address with: ua transport port).
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
callId [
<category: 'info'>
^ initial_dialog callId
]
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 logNotice: ('SIPCall(<1s>) dialog is confirmed now.'
expandMacrosWith: self callId) 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'>
self logError: ('<1p>(<2s>) unhandled request <3p>.'
expandMacrosWithArguments: {self class. self callId. aRequest class verb})
area: #sip.
]
]
SIPSessionBase subclass: SIPCall [
| sdp_offer sdp_result invite state |
<category: 'OsmoSIP-Callagent'>

View File

@ -0,0 +1,109 @@
"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
<category: 'OsmoSIP-Callagent'>
<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@<1p>:<2p>'
expandMacrosWith: ua transport address with: ua transport port).
]
useragent: aUseragent [
<category: 'creation'>
ua := aUseragent
]
callId [
<category: 'info'>
^ initial_dialog callId
]
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 logNotice: ('SIPCall(<1s>) dialog is confirmed now.'
expandMacrosWith: self callId) 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'>
self logError: ('<1p>(<2s>) unhandled request <3p>.'
expandMacrosWithArguments: {self class. self callId. aRequest class verb})
area: #sip.
]
]

View File

@ -39,7 +39,10 @@
<filein>callagent/transactions/SIPInviteTransaction.st</filein>
<filein>callagent/SIPCallAgent.st</filein>
<filein>callagent/SIPCall.st</filein>
<filein>callagent/session/Extensions.st</filein>
<filein>callagent/session/SIPSessionBase.st</filein>
<filein>callagent/session/SIPCall.st</filein>
<filein>callagent/transport/SIPTransport.st</filein>
<filein>callagent/transport/SIPUdpTransport.st</filein>