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

callagent: Start to deal with requests in new dialogs

* This isn't doing proper routing (e.g. the via is not modified
  properly but we return it to the right address)
* An unknown BYE will be acked with a 481. The 'respondWith:...'
  includes the wrong 'Allow:' but it is good enough from the
  structure for now.
* Re-Order the loading of files as the SIPUserAgent is extended
  the SIPRequests.
* Add the port/ip to the SIPDialog so that responding to the
  request is possible.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-06 01:17:36 +02:00
parent 5b1b3f891d
commit 55765c9f0d
3 changed files with 46 additions and 6 deletions

View File

@ -18,6 +18,25 @@
PackageLoader fileInPackage: 'Sockets'.
SIPRequest extend [
sipDispatchNewDialog: aDialog on: aUserAgent [
<category: 'OsmoSIP-Callagent'>
self logError: 'Unknown action for ', self class name area: #sip.
]
]
SIPByeRequest extend [
sipDispatchNewDialog: aDialog on: aUserAgent [
<category: 'OsmoSIP-Callagent'>
self logNotice: 'Unknown call ', self class name area: #sip.
aUserAgent
respondWith: 481
phrase: 'Call/Transaction Does Not Existing'
on: self
dialog: aDialog.
]
]
Object subclass: SIPTransport [
| queue handler |
<category: 'OsmoSIP-Callagent'>
@ -271,17 +290,22 @@ SIPUserAgentBase subclass: SIPUserAgent [
% {self. aTransaction} area: #sip.]].
]
dispatchRequest: aReq [
dispatchRequest: aReq data: aDatagram [
| dialogs dialog |
<category: 'dispatch'>
dialog := SIPDialog fromMessage: aReq.
dialog := (SIPDialog fromMessage: aReq)
destIp: aDatagram address displayString;
destPort: aDatagram port;
yourself.
dialogs := sem critical: [self dialogs copy].
dialogs do: [:each |
(each isCompatible: dialog) ifTrue: [
each newRequest: aReq.
^ self
]]
]].
self newDialog: dialog request: aReq.
]
dispatchResponse: aReq [
@ -328,7 +352,7 @@ SIPUserAgentBase subclass: SIPUserAgent [
].
req isRequest
ifTrue: [self dispatchRequest: req]
ifTrue: [self dispatchRequest: req data: aData]
ifFalse: [self dispatchResponse: req].
] on: Error do: [:e |
e logException: 'Parsing error %1' % {e tag} area: #sip.
@ -353,4 +377,12 @@ SIPUserAgentBase subclass: SIPUserAgent [
self injectDefaults: resp.
self queueData: resp asDatagram dialog: dialog.
]
newDialog: aDialog request: aRequest [
<category: 'We have a new dialog'>
"This might be a re-transmit of a BYE. So we will use the
double dispatch to check what we should do with this dialog."
aRequest sipDispatchNewDialog: aDialog on: self.
]
]

View File

@ -161,6 +161,14 @@ Object subclass: SIPDialog [
^ dest_port
]
destIp: aIP [
dest_ip := aIP
]
destPort: aPort [
dest_port := aPort
]
isCompatible: aDialog [
<category: 'check'>
"I check if the remote and the local dialog match. I do this by cross

View File

@ -5,15 +5,15 @@
<filein>grammar/SIPGrammar.st</filein>
<filein>callagent/Base64MimeConverter.st</filein>
<filein>callagent/SIPCallAgent.st</filein>
<filein>callagent/SIPDialog.st</filein>
<filein>callagent/SIPLogArea.st</filein>
<filein>callagent/SIPDialog.st</filein>
<filein>callagent/SIPParams.st</filein>
<filein>callagent/SIPParser.st</filein>
<filein>callagent/SIPRandom.st</filein>
<filein>callagent/SIPRequests.st</filein>
<filein>callagent/SIPResponse.st</filein>
<filein>callagent/SIPTransactions.st</filein>
<filein>callagent/SIPCallAgent.st</filein>
<filein>callagent/SIPCall.st</filein>
<test>