smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/callagent/authorization/SIPAuthorization.st

125 lines
3.2 KiB
Smalltalk

"
(C) 2011,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/>.
"
Object subclass: SIPAuthorization [
| username realm nonce operation uri response |
<category: 'OsmoSIP-authorization'>
<comment: 'I help with the Authorization parameter inside
messages. E.g. with the INVITE'>
SIPAuthorization class >> validCalls [
^#(#username: #realm: #nonce: #uri: #response:)
]
SIPAuthorization class >> from: anArray [
| res |
"I parse the result of the parser"
res := self new.
anArray do: [:each |
| call |
call := (each first, ':') asSymbol.
(self validCalls includes: call)
ifTrue: [res perform: call with: each third]
ifFalse: [
self logNotice: ('<1p> unhandled option <2p>'
expandMacrosWithArguments: {self class. each first}) area: #sip]].
^res
]
username [
<category: 'accessing'>
^username
]
realm [
<category: 'accessing'>
^realm
]
nonce [
<category: 'accessing'>
^nonce
]
uri [
<category: 'accessing'>
^uri
]
response [
<category: 'accessing'>
^response
]
response: aResponse [
<category: 'internal'>
response := aResponse
]
username: aUsername [
<category: 'accessing'>
username := aUsername
]
realm: aRealm [
<category: 'accessing'>
realm := aRealm
]
nonce: aNonce [
<category: 'accessing'>
nonce := aNonce
]
uri: anUri [
<category: 'accessing'>
uri := anUri
]
calculateResponse: aPassword operation: anOperationName [
response := SIPDigest
authUser: username
password: aPassword
realm: realm
nonce: nonce
operation: anOperationName
url: uri.
]
do: aBlock [
(String streamContents: [:str | self nextPutAllOn: str]) do: aBlock
]
nextPutAllOn: aStream [
aStream
nextPutAll: 'Digest username="';
nextPutAll: username;
nextPutAll: '", realm="';
nextPutAll: realm;
nextPutAll: '", nonce="';
nextPutAll: nonce;
nextPutAll: '", uri="';
nextPutAll: uri;
nextPutAll: '", algorithm=MD5, response="';
nextPutAll: response;
nextPutAll: '"'.
]
]