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

identity: Make the SIPSession work based on identity

This commit is contained in:
Holger Hans Peter Freyther 2014-04-03 11:05:08 +02:00
parent 858d25e2be
commit 3779496a4a
5 changed files with 78 additions and 7 deletions

View File

@ -17,12 +17,21 @@
"
Object subclass: SIPIdentity [
| username password proxyUsername proxyPassword |
| hostname username password proxyUsername proxyPassword |
<category: 'OsmoSIP-authorization'>
<comment: 'I represent a local identity that initiated a session
or similar'>
SIPIdentity class >> fromUserString: aString [
| split |
split := aString subStrings: '@'.
^self new
username: split first;
hostname: split second;
yourself
]
username: aUsername [
username := aUsername
]
@ -31,6 +40,10 @@ Object subclass: SIPIdentity [
password := aPassword
]
hostname: aHostname [
hostname := aHostname
]
proxyUsername: aUsername [
proxyUsername := aUsername
]
@ -47,6 +60,10 @@ Object subclass: SIPIdentity [
^password
]
hostname [
^hostname
]
proxyUsername [
^proxyUsername ifNil: [username]
]
@ -54,4 +71,12 @@ Object subclass: SIPIdentity [
proxyPassword [
^proxyPassword ifNil: [password]
]
userString [
^(WriteStream on: String new)
nextPutAll: username;
nextPut: $@;
nextPutAll: hostname;
contents
]
]

View File

@ -51,11 +51,21 @@ will simply ignore everything but the first dialog.'>
]
]
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
<category: 'creation'>
SIPCall class >> fromIdenity: anIdentity host: aHost port: aPort to: aTo on: aUseragent [
^ self
on: ((SIPDialog fromUser: aUser host: aHost port: aPort)
to: aTo; yourself) useragent: aUseragent
on: ((SIPDialog fromUser: anIdentity userString host: aHost port: aPort)
to: aTo; yourself) useragent: aUseragent identity: anIdentity
]
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
| identity array |
<category: 'creation'>
array := aUser subStrings: '@'.
identity := SIPIdentity new
username: array first;
hostname: array second;
yourself.
^self fromIdenity: identity host: aHost port: aPort to: aTo on: aUseragent
]
state [

View File

@ -25,15 +25,20 @@ 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 [
SIPSessionBase class >> on: aDialog useragent: aUseragent identity: anIdentity [
<category: 'creation'>
^ self new
useragent: aUseragent;
identity: aUseragent mainIdentity;
identity: anIdentity;
initialDialog: aDialog;
yourself
]
SIPSessionBase class >> on: aDialog useragent: aUseragent [
<category: 'creation'>
^self on: aDialog useragent: aUseragent identity: aUseragent mainIdentity
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog.

View File

@ -0,0 +1,29 @@
"
(C) 2014 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/>.
"
TestCase subclass: SIPIdentityTest [
<category: 'OsmoSIP-Tests'>
<comment: 'I do test some basics of the SIPIdentity class'>
testFromUserString [
| res |
res := SIPIdentity fromUserString: '1234@10.23.24.1'.
self assert: res username equals: '1234'.
self assert: res hostname equals: '10.23.24.1'.
]
]

View File

@ -68,6 +68,7 @@
<sunit>Osmo.SIPCallAgentTest</sunit>
<sunit>Osmo.SIPDigestTest</sunit>
<sunit>Osmo.SIPRegisterTransactionTest</sunit>
<sunit>Osmo.SIPIdentityTest</sunit>
<filein>grammar/SIPGrammarTest.st</filein>
<filein>callagent/tests/SIPParserTest.st</filein>
<filein>callagent/tests/Tests.st</filein>
@ -75,5 +76,6 @@
<filein>callagent/tests/SIPDigestTest.st</filein>
<filein>callagent/tests/SIPTransportMock.st</filein>
<filein>callagent/tests/SIPRegisterTransactionTest.st</filein>
<filein>callagent/tests/SIPIdentityTest.st</filein>
</test>
</package>