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

identity: Remove direct usage of of useragent username

In preparation of introducing multiple identities we need to
remove usage of SIPUserAgent>>#username. The next step is to
actually be able to pass a different identity.
This commit is contained in:
Holger Hans Peter Freyther 2014-04-02 18:28:09 +02:00
parent 89efe79f71
commit 858d25e2be
4 changed files with 23 additions and 26 deletions

View File

@ -48,10 +48,10 @@ Object subclass: SIPIdentity [
]
proxyUsername [
^proxyUsername
^proxyUsername ifNil: [username]
]
proxyPassword [
^proxyPassword
^proxyPassword ifNil: [password]
]
]

View File

@ -17,7 +17,7 @@
"
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
| rem ua identity 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
@ -29,6 +29,7 @@ a proper session.'>
<category: 'creation'>
^ self new
useragent: aUseragent;
identity: aUseragent mainIdentity;
initialDialog: aDialog;
yourself
]
@ -37,7 +38,7 @@ a proper session.'>
<category: 'creation'>
initial_dialog := aDialog.
initial_dialog contact: ('sip:<1s>@<2p>:<3p>'
expandMacrosWith: ua username with: ua transport address with: ua transport port).
expandMacrosWith: identity username with: ua transport address with: ua transport port).
]
useragent: aUseragent [
@ -45,6 +46,11 @@ a proper session.'>
ua := aUseragent
]
identity: anIdentity [
<category: 'creation'>
identity := anIdentity
]
callId [
<category: 'info'>
^ initial_dialog callId

View File

@ -18,7 +18,7 @@
Object subclass: SIPTransaction [
| sem useragent initial_dialog state timeout success failure notification
cseq branch retransmit_time fail_time removal
cseq branch retransmit_time fail_time removal identity
authorization last_was_auth proxy_authorization last_was_proxy_auth |
<category: 'OsmoSIP-Callagent'>
@ -36,6 +36,7 @@ Object subclass: SIPTransaction [
<category: 'creation'>
^ self new
initialize;
identity: aUA mainIdentity;
userAgent: aUA;
initialDialog: aDialog;
setupTransaction: aCseq;
@ -73,6 +74,11 @@ Object subclass: SIPTransaction [
useragent := aUA
]
identity: anIdentity [
<category: 'creation'>
identity := anIdentity
]
state [
<category: 'state'>
^ state ifNil: [^ self class stateInitial]
@ -180,13 +186,13 @@ Object subclass: SIPTransaction [
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
authorization := SIPAuthorization new
username: useragent username;
username: identity username;
realm: (auth at: 'realm');
nonce: (auth at: 'nonce');
uri: initial_dialog destinationAddress;
yourself.
authorization
calculateResponse: useragent password
calculateResponse: identity password
operation: self class operationName.
"Increase CSeq and generate a new branch"
@ -221,7 +227,7 @@ Object subclass: SIPTransaction [
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
proxy_authorization := SIPProxyAuthorization new
username: useragent proxyUsername;
username: identity proxyUsername;
realm: (auth at: 'realm');
nonce: (auth at: 'nonce');
qop: (auth at: 'qop');
@ -363,7 +369,7 @@ Object subclass: SIPTransaction [
proxy_authorization ifNotNil: [
proxy_authorization incrementClientNonce.
proxy_authorization
calculateResponse: useragent proxyPassword
calculateResponse: identity proxyPassword
operation: self class operationName.
aRequest addParameter: 'Proxy-Authorization' value: proxy_authorization].
]

View File

@ -184,27 +184,12 @@ SIPUserAgentBase subclass: SIPUserAgent [
mainIdentity username: aUser.
]
username [
<category: 'accessing'>
^mainIdentity username
]
password: aPass [
<category: 'accessing'>
mainIdentity password: aPass
]
password [
<category: 'accessing'>
^mainIdentity password
mainIdentity [
^mainIdentity
]
proxyUsername [
^mainIdentity proxyUsername ifNil: [mainIdentity username]
]
proxyPassword [
^mainIdentity proxyPassword ifNil: [mainIdentity password]
]
]