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

identity: Move the identity into the SIPDialog

This way the one that creates a dialog needs to decide which
identity will be used.
This commit is contained in:
Holger Hans Peter Freyther 2014-04-22 14:18:26 +02:00
parent 3779496a4a
commit 0c609b9975
6 changed files with 37 additions and 40 deletions

View File

@ -18,8 +18,10 @@
Object subclass: SIPDialog [
| from from_tag to to_tag dest_ip dest_port is_client call_id
state contact cseq |
<comment: 'I represent a dialog between two parties'>
state contact cseq identity |
<comment: 'I represent a dialog between two parties.
TODO: from and identity are redundant. These need to be
united into one.'>
<category: 'OsmoSIP-Callagent'>
SIPDialog class >> stateUnconfirmed [ <category: 'state'> ^ #unconfirmed ]
@ -73,6 +75,14 @@ Object subclass: SIPDialog [
^ stream contents.
]
identity: anIdentity [
<category: 'direction'>
identity := anIdentity
]
identity [
^identity
]
isClient [
<category: 'direction'>

View File

@ -17,7 +17,7 @@
"
Object subclass: SIPIdentity [
| hostname username password proxyUsername proxyPassword |
| contact hostname username password proxyUsername proxyPassword |
<category: 'OsmoSIP-authorization'>
<comment: 'I represent a local identity that initiated a session
@ -32,6 +32,10 @@ Object subclass: SIPIdentity [
yourself
]
contact: aContact [
contact := aContact
]
username: aUsername [
username := aUsername
]
@ -73,10 +77,11 @@ Object subclass: SIPIdentity [
]
userString [
^(WriteStream on: String new)
nextPutAll: username;
nextPut: $@;
nextPutAll: hostname;
contents
^contact ifNil: [
(WriteStream on: String new)
nextPutAll: username;
nextPut: $@;
nextPutAll: hostname;
contents]
]
]

View File

@ -1,5 +1,5 @@
"
(C) 2011 by Holger Hans Peter Freyther
(C) 2011, 2014 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -54,16 +54,14 @@ will simply ignore everything but the first dialog.'>
SIPCall class >> fromIdenity: anIdentity host: aHost port: aPort to: aTo on: aUseragent [
^ self
on: ((SIPDialog fromUser: anIdentity userString host: aHost port: aPort)
to: aTo; yourself) useragent: aUseragent identity: anIdentity
to: aTo; identity: anIdentity; yourself) useragent: aUseragent
]
SIPCall class >> fromUser: aUser host: aHost port: aPort to: aTo on: aUseragent [
| identity array |
| identity |
<category: 'creation'>
array := aUser subStrings: '@'.
identity := SIPIdentity new
username: array first;
hostname: array second;
identity := aUseragent mainIdentity copy
contact: aUser;
yourself.
^self fromIdenity: identity host: aHost port: aPort to: aTo on: aUseragent
]

View File

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

View File

@ -63,6 +63,7 @@ TestCase subclass: SIPRegisterTransactionTest [
password: 'st'.
dialog := SIPDialog fromUser: 'sip:st@127.0.0.1' host: '127.0.0.1' port: 5060.
dialog identity: agent mainIdentity.
]
testSimpleRegister [

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