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

proxy: Handle ProxyAuthenticate/ProxyAuthorize

Add a testcase for testing ProxyAuthenticate and ProxyAuthorize,
extend the grammar and parser to handle the needed bits. Document
another error/failure with the dialog handling code and create a
testcase that fully connects a call.
This commit is contained in:
Holger Hans Peter Freyther 2014-03-17 20:06:03 +01:00
parent 3dd23b46dd
commit fd1d3829ad
10 changed files with 327 additions and 10 deletions

4
TODO
View File

@ -18,6 +18,10 @@ Transaction:
Dialog/Session/Route-Set:
* A dialog should have a route set (with the Via's)
* Does a dialog hold a session? a session holds a dialog?
* A call can go to session without having a confirmed dialog. This needs
to be looked at/denied. Do not ack a call that has no ;tag= attribute
for. One can remove the from ;tag in the "200 OK" test result to provoke
the failure in the testProxyAuth testcase.
General:
* 401 handling might not work for BYE,ACK. For ACK the ACK might not

View File

@ -0,0 +1,113 @@
"
(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/>.
"
SIPAuthorization subclass: SIPProxyAuthorization [
| qop clientNonce nonceCount |
<category: 'OsmoSIP-authorization'>
<comment: 'I help with the proxy authorization'>
SIPProxyAuthorization class >> validCalls [
^super validCalls, #(#qop: #cnonce: #nc:)
]
SIPProxyAuthorization class >> formatNonceCount: aCount [
^aCount printPaddedWith: $0 to: 8.
]
SIPProxyAuthorization class >> new [
^super new
initialize;
yourself
]
initialize [
nonceCount := 0.
]
qop [
<category: 'accessing'>
^qop
]
qop: aQop [
<category: 'accessing'>
qop := aQop
]
cnonce: aCNonce [
aCNonce size = 8 ifFalse: [^self error: 'clientNonce needs to be eight chars'].
clientNonce := aCNonce
]
cnonce [
^clientNonce
]
clientNonce [
^clientNonce
]
nonceCount: aCount [
nonceCount := aCount
]
nc: aCount [
^self nonceCount: aCount
]
nonceCount [
^nonceCount
]
incrementClientNonce [
nonceCount := nonceCount + 1.
]
calculateResponse: aPassword operation: anOperationName [
response := SIPDigest
authUser: username
password: aPassword
realm: realm
nonce: nonce
operation: anOperationName
url: uri
qop: qop
clientNonce: clientNonce
nonceCount: (self class formatNonceCount: nonceCount).
]
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: '", cnonce=';
nextPutAll: clientNonce;
nextPutAll: ', qop=';
nextPutAll: qop;
nextPutAll: ', nc=';
nextPutAll: (self class formatNonceCount: nonceCount).
]
]

View File

@ -33,8 +33,7 @@ Object subclass: SIPURandom [
]
]
SIPURandom class >> nextInt [
<category: 'random'>
SIPURandom class >> nextFourBytes [
| file |
file := FileDescriptor open: '/dev/urandom' mode: 'r'.
[
@ -44,9 +43,18 @@ Object subclass: SIPURandom [
data at: each put: file next value.
].
^ data uintAt: 1
^data
] ensure: [
file close.
]
]
SIPURandom class >> nextInt [
<category: 'random'>
^self nextFourBytes uintAt: 1
]
SIPURandom class >> newClientNonce [
^self nextFourBytes hex
]
]

View File

@ -150,6 +150,14 @@ SIPGrammar subclass: SIPParser [
with: nodes third asLowercase = 'true']
]
qop_options [
"TODO: There can be multiple auth options to pick from"
^super qop_options => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes fourth].
]
challenge [
^super challenge => [:nodes |
@ -194,4 +202,17 @@ SIPGrammar subclass: SIPParser [
with: nodes second
with: (SIPAuthorization from: params)]
]
ProxyAuthorization [
^super ProxyAuthorization => [:nodes |
| params |
params := OrderedCollection new.
params add: nodes third third first.
nodes third third second do: [:each |
params add: each second].
Array
with: nodes first
with: nodes second
with: (SIPProxyAuthorization from: params)]
]
]

View File

@ -51,6 +51,19 @@ TestCase subclass: SIPCallAgentTest [
contents
]
ok: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 200 OK'; cr; nl;
nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
nextPutAll: 'CSeq: '; nextPutAll: aCseq displayString; nextPutAll: ' INVITE'; cr; nl;
nextPutAll: 'From: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
nextPutAll: 'To: <sip:st@127.0.0.1>;tag=123'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
cr; nl;
contents
]
invalidAuthorizationRequired: aBranch callId: aCallId tag: aTag [
"This is missing WWW-Authenticate so it is kind of invalid"
^(WriteStream on: String new)
@ -87,6 +100,22 @@ TestCase subclass: SIPCallAgentTest [
contents
]
proxyAuthRequired: aBranch callId: aCallId tag: aTag cseq: aCseq [
^(WriteStream on: String new)
nextPutAll: 'SIP/2.0 407 Proxy Authentication Required'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 127.0.0.1:5060;branch='; nextPutAll: aBranch; cr; nl;
nextPutAll: 'Proxy-Authenticate: Digest realm="07440491",qop="auth",nonce="06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8",algorithm=MD5'; cr; nl;
nextPutAll: 'From: <sip:st@127.0.0.1>;tag='; nextPutAll: aTag; cr; nl;
nextPutAll: 'To: <sip:st@127.0.0.1>'; cr; nl;
nextPutAll: 'Call-ID: '; nextPutAll: aCallId; cr; nl;
nextPutAll: 'CSeq: '; nextPutAll: aCseq displayString; nextPutAll: ' INVITE'; cr; nl;
nextPutAll: 'Server: YATE/5.1.0'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
cr; nl;
contents
]
setUp [
sent := OrderedCollection new.
transport := SIPTransportMock new
@ -211,6 +240,70 @@ TestCase subclass: SIPCallAgentTest [
self assert: call state equals: #failed.
]
testWithProxyAuth [
| call msg branch callId fromTag auth secondBranch origCnonce |
call := SIPCall fromUser: 'sip:sip@test' host: '127.0.0.1' port: 5060 to: 'sip:127.0.0.1' on: agent.
call createCall: 'dummy-sdp'.
"First assertions for the invite"
self assert: sent size equals: 1.
msg := SIPParser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
"Now inject an auth requirement message"
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
transport inject: (self proxyAuthRequired: branch callId: callId tag: fromTag tag cseq: 1).
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 2.
msg := SIPParser parse: sent second data.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
self assert: call state equals: SIPCall stateInvite.
"Verify the auth part of the message"
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
self deny: auth isNil.
self assert: auth username equals: 'st'.
self assert: auth realm equals: '07440491'.
self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth nonce equals: '06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8'.
self assert: auth qop equals: 'auth'.
self assert: auth nonceCount equals: '00000001'.
"Fields that depend on the random clientNonce"
self assert: auth response size equals: 32.
self assert: auth clientNonce size equals: 8.
origCnonce := auth clientNonce.
"Inject a 200 and check the ACK"
transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: 2).
self assert: sent size equals: 3.
msg := SIPParser parse: sent third data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
self assert: call state equals: SIPCall stateSession.
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
self deny: auth isNil.
self assert: auth username equals: 'st'.
self assert: auth realm equals: '07440491'.
self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth nonce equals: '06fafd01e9aade68c8400db8c9c146a7bfc5bc28C0A4AC1EE6A8'.
self assert: auth qop equals: 'auth'.
self assert: auth nonceCount equals: '00000002'.
self assert: auth clientNonce equals: origCnonce.
"And let it timeout.. With better code and the clientNonce
being stored in the call/initial dialog we could even add
the Proxy-Authorization to the BYE message.."
call hangup.
]
testInviteWithRedirect [
| call msg branch callId fromTag |

View File

@ -175,6 +175,7 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
nextPutAll: 'Call-ID: fc0f7969-8b91-e311-8101-844bf52a8297@xiaoyu'; cr; nl;
nextPutAll: 'CSeq: 7 REGISTER'; cr; nl;
nextPutAll: 'WWW-Authenticate: Digest realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", stale=TRUE, algorithm=MD5'; cr; nl;
nextPutAll: 'Proxy-Authenticate: Digest realm="07440491",qop="auth",nonce="7a7155d2bff57ffcc226f0e6819d00be68d517b3C0A4ABEB5BE0",algorithm=MD5'; cr; nl;
nextPutAll: 'Server: YATE/5.1.0'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
@ -193,6 +194,16 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
self assert: (res parameter: 'cAlL-Id') equals: 'fc0f7969-8b91-e311-8101-844bf52a8297@xiaoyu'.
]
testProxyAuthenticate [
| res auth |
res := self parse: self resultUnauthorized.
auth := res parameter: 'Proxy-Authenticate'.
self assert: (auth at: 'realm') equals: '07440491'.
self assert: (auth at: 'nonce') equals: '7a7155d2bff57ffcc226f0e6819d00be68d517b3C0A4ABEB5BE0'.
self assert: (auth at: 'algorithm') equals: 'MD5'.
self assert: (auth at: 'qop') equals: 'auth'.
]
authorizationData [
"Shortened because we only care about Authorization"
^(WriteStream on: String new)

View File

@ -19,7 +19,7 @@
Object subclass: SIPTransaction [
| sem useragent initial_dialog state timeout success failure notification
cseq branch retransmit_time fail_time removal
authorization last_was_auth |
authorization last_was_auth proxy_authorization last_was_proxy_auth |
<category: 'OsmoSIP-Callagent'>
@ -60,6 +60,7 @@ Object subclass: SIPTransaction [
<category: 'creation'>
sem := RecursionLock new.
last_was_auth := false.
last_was_proxy_auth := false.
]
initialDialog: aDialog [
@ -196,6 +197,46 @@ Object subclass: SIPTransaction [
self retransmit.
]
respProxyAuthRequired: aResp dialog: aDialog [
| auth |
<category: 'private-dispatch'>
"TODO... fix the duplication"
"We are running in circles so better cancel it. Not quite correct
though. There could be multiple proxies. So we should compare the
realm, nonce, etc. We would actually need to have a list of proxy
auths for full spec compliance."
last_was_proxy_auth ifTrue: [
^self respFailure: aResp dialog: aDialog].
last_was_proxy_auth := true.
auth := aResp parameter: 'Proxy-Authenticate' ifAbsent: [nil].
auth ifNil: [^self wrongAuth: aResp dialog: aDialog].
((auth at: 'algorithm') = 'MD5')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
((auth at: 'qop') = 'auth')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
proxy_authorization := SIPProxyAuthorization new
username: useragent username;
realm: (auth at: 'realm');
nonce: (auth at: 'nonce');
qop: (auth at: 'qop');
cnonce: SIPURandom newClientNonce;
uri: initial_dialog destinationAddress;
yourself.
"Increase CSeq and generate a new branch"
cseq := cseq + 1.
branch := useragent class generateBranch.
"Now start again with the auth part"
self retransmit.
]
checkSequenceNumber: aReq [
| new_cseq |
<category: 'private-dispatch'>
@ -254,15 +295,23 @@ Object subclass: SIPTransaction [
code = 200 ifTrue: [
last_was_auth := false.
last_was_proxy_auth := false.
^ self respSuccess: aResp dialog: dialog
].
code = 401 ifTrue: [
last_was_proxy_auth := false.
^self respAuthRequired: aResp dialog: dialog.
].
code = 407 ifTrue: [
last_was_auth := false.
^self respProxyAuthRequired: aResp dialog: dialog.
].
code > 200 ifTrue: [
last_was_auth := false.
last_was_proxy_auth := false.
^ self respFailure: aResp dialog: dialog
]
]
@ -309,8 +358,14 @@ Object subclass: SIPTransaction [
addAuthorizationTo: aRequest [
<category: 'authentication'>
authorization ifNil: [^self].
aRequest addParameter: 'Authorization' value: authorization.
authorization ifNotNil: [
aRequest addParameter: 'Authorization' value: authorization].
proxy_authorization ifNotNil: [
proxy_authorization incrementClientNonce.
proxy_authorization
calculateResponse: useragent password
operation: self class operationName.
aRequest addParameter: 'Proxy-Authorization' value: proxy_authorization].
]
createInvite: sdp [

View File

@ -309,8 +309,8 @@ PP.PPCompositeParser subclass: SIPGrammar [
<category: 'generic'>
^ (self Via / self CSeq / self From /
self To / self Contact / self WWWAuthenticate / self Authorization /
extension_header), CRLF
self To / self Contact / self WWWAuthenticate / self ProxyAuthenticate /
self Authorization / self ProxyAuthorization / extension_header), CRLF
]
message_body [
@ -548,7 +548,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
message_qop [
<category: 'WWW-Authenticate'>
^'qop' asParser, EQUAL, self qop_value
^'qop' asParser, EQUAL, self qop_value flatten
]
cnonce [
@ -636,7 +636,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
qop_options [
| qop_value |
<category: 'WWW-Authenticate'>
qop_value := self qop_value.
qop_value := self qop_value flatten.
^ 'qop' asParser, EQUAL, LDQUOT, qop_value, ($, asParser, qop_value) star, RDQUOT
]
@ -665,6 +665,16 @@ PP.PPCompositeParser subclass: SIPGrammar [
^self token
]
ProxyAuthenticate [
<category: 'Proxy-Authenticate'>
^'Proxy-Authenticate' asParser, HCOLON, self challenge
]
ProxyAuthorization [
<category: 'Proxy-Authenticate'>
^'Proxy-Authorization' asParser, HCOLON, self credentials
]
contact_param [
<category: 'contact'>
^ (self name_addr / self addr_spec), (SEMI, self contact_params) star

View File

@ -323,6 +323,7 @@ PP.PPCompositeParserTest subclass: SIPGrammarTest [
nextPutAll: 'Call-ID: fc0f7969-8b91-e311-8101-844bf52a8297@xiaoyu'; cr; nl;
nextPutAll: 'CSeq: 7 REGISTER'; cr; nl;
nextPutAll: 'WWW-Authenticate: Digest realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", stale=TRUE, algorithm=MD5'; cr; nl;
nextPutAll: 'Proxy-Authenticate: Digest realm="07440491",qop="auth",nonce="7a7155d2bff57ffcc226f0e6819d00be68d517b3C0A4ABEB5BE0",algorithm=MD5'; cr; nl;
nextPutAll: 'Server: YATE/5.1.0'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;

View File

@ -56,6 +56,7 @@
<filein>callagent/transport/SIPUdpTransport.st</filein>
<filein>callagent/authorization/SIPDigest.st</filein>
<filein>callagent/authorization/SIPAuthorization.st</filein>
<filein>callagent/authorization/SIPProxyAuthorization.st</filein>
<test>
<prereq>PetitParserTests</prereq>