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

digest: Implement the digest authentication for SIP

This only implements one of the possible approaches for the digest
handling. This is a very simple test and the choiche of the same
username/password was a bit unfortunate.
This commit is contained in:
Holger Hans Peter Freyther 2014-02-13 12:09:00 +01:00
parent abc1a933fd
commit 193126c287
4 changed files with 90 additions and 0 deletions

28
callagent/Extensions.st Normal file
View File

@ -0,0 +1,28 @@
"
Extensions coming from Pharo
"
ByteArray extend [
hex [
<category: '*PharoCompat'>
" an alternate implementation was | result stream |
result := String new: self size * 2.
stream := result writeStream.
1 to: self size do: [ :ix | |each|
each := self at: ix.
stream
nextPut: ('0123456789ABCDEF' at: each // 16 + 1);
nextPut: ('0123456789ABCDEF' at: each \\ 16 + 1)].
^ result"
"Answer a hexa decimal representation of the receiver"
| string v index map |
map := '0123456789abcdef'.
string := String new: self size * 2. "hex"
index := 0.
1 to: self size do: [ :i |
v := self at: i.
string at: (index := index + 1) put: (map at: (v bitShift: -4) + 1).
string at: (index := index + 1) put: (map at: (v bitAnd: 15) + 1)].
^string
]
]

47
callagent/SIPDigest.st Normal file
View File

@ -0,0 +1,47 @@
"
(C) 2011 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: SIPDigest [
<category: 'OsmoSIP-Callagent-Auth'>
<comment: 'I help in generating a response to a nonce/digest
request.'>
SIPDigest class >> authUser: aName password: aPassword realm: aRealm nonce: aNonce operation: anOperation url: aSipUrlString [
| ha1 ha2 resp md5 |
ha1 := (MD5 new
nextPutAll: aName;
nextPutAll: ':';
nextPutAll: aRealm;
nextPutAll: ':';
nextPutAll: aPassword;
digest) hex.
ha2 := (MD5 new
nextPutAll: anOperation;
nextPutAll: ':';
nextPutAll: aSipUrlString;
digest) hex.
^(MD5 new
nextPutAll: ha1;
nextPutAll: ':';
nextPutAll: aNonce;
nextPutAll: ':';
nextPutAll: ha2;
digest) hex
]
]

View File

@ -0,0 +1,10 @@
TestCase subclass: SIPDigestTest [
<category: 'OsmoSIP-Callagent-Tests'>
<comment: 'I test the digest implemetnation'>
testSimpleDigest [
| res |
res := SIPDigest authUser: 'st' password: 'st' realm: 'Yate' nonce: '373ef30b297545cbce99fad09f1409cb.1392124197' operation: 'REGISTER' url: 'sip:127.0.0.2'.
self assert: res equals: '987937460705015b6575176176d7c739'.
]
]

View File

@ -6,12 +6,15 @@
<prereq>OsmoNetwork</prereq>
<prereq>Sockets</prereq>
<prereq>PetitParser</prereq>
<prereq>Digest</prereq>
<filein>grammar/SIPGrammar.st</filein>
<filein>callagent/Base64MimeConverter.st</filein>
<filein>callagent/Extensions.st</filein>
<filein>callagent/SIPLogArea.st</filein>
<filein>callagent/SIPDialog.st</filein>
<filein>callagent/SIPDigest.st</filein>
<filein>callagent/SIPParams.st</filein>
<filein>callagent/SIPParser.st</filein>
<filein>callagent/SIPRandom.st</filein>
@ -29,8 +32,10 @@
<sunit>Osmo.SIPParserTest</sunit>
<sunit>Osmo.SIPRequestTest</sunit>
<sunit>Osmo.SIPUdpTransportTest</sunit>
<sunit>Osmo.SIPDigestTest</sunit>
<filein>grammar/SIPGrammarTest.st</filein>
<filein>callagent/SIPParserTest.st</filein>
<filein>callagent/Tests.st</filein>
<filein>callagent/tests/SIPDigestTest.st</filein>
</test>
</package>