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

authorization: Parse the Authorization parse of a SIP request

This commit is contained in:
Holger Hans Peter Freyther 2014-02-14 17:23:42 +01:00
parent 903594e07d
commit 7294d8add0
5 changed files with 189 additions and 8 deletions

View File

@ -170,4 +170,37 @@ SIPGrammar subclass: SIPParser [
d at: (nodes at: 3) first put: (nodes at: 3) third.
d]
]
request_digest [
^super request_digest => [:nodes | nodes second]
]
digest_uri [
^super digest_uri => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes fourth]
]
username [
^super username => [:nodes |
Array
with: nodes first
with: nodes second
with: nodes third third]
]
Authorization [
^super Authorization => [: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: (SIPAuthorization from: params)]
]
]

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
@ -191,4 +191,27 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
self assert: (auth at: 'stale').
self assert: (auth at: 'algorithm') equals: 'MD5'.
]
authorizationData [
"Shortened because we only care about Authorization"
^(WriteStream on: String new)
nextPutAll: 'INVITE sip:127.0.0.1 SIP/2.0'; cr; nl;
nextPutAll: 'Via: SIP/2.0/MOCK 127.0.0.1:5060;branch=z9hG4bKMz'; cr; nl;
nextPutAll: 'Authorization: Digest username="st", realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", uri="sip:127.0.0.1", algorithm=MD5, response="bc8dfaa413e897863dbab4c622e4b9b4"'; cr; nl;
cr; nl;
contents
]
testAuthorization [
| res auth|
res := self parse: self authorizationData.
auth := res parameter: 'Authorization' ifAbsent: [nil].
self deny: auth isNil.
self assert: auth username equals: 'st'.
self assert: auth realm equals: 'Yate'.
self assert: auth nonce equals: '373ef30b297545cbce99fad09f1409cb.1392124197'.
self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'.
]
]

View File

@ -17,11 +17,62 @@
"
Object subclass: SIPAuthorization [
| username realm nonce algorithm operation uri response |
| 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
@ -37,11 +88,6 @@ Object subclass: SIPAuthorization [
nonce := aNonce
]
algorithm: anAlgorithm [
<category: 'accessing'>
algorithm := anAlgorithm
]
uri: anUri [
<category: 'accessing'>
uri := anUri

View File

@ -179,6 +179,11 @@ PP.PPCompositeParser subclass: SIPGrammar [
$D asParser / $E asParser / $F asParser
]
LHEX [
^ #digit asParser / $a asParser / $b asParser / $c asParser /
$d asParser / $e asParser / $f asParser
]
unreserved [
<category: 'generic'>
^ (#letter asParser / #digit asParser) / self mark
@ -304,7 +309,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
<category: 'generic'>
^ (self Via / self CSeq / self From /
self To / self Contact / self WWWAuthenticate /
self To / self Contact / self WWWAuthenticate / self Authorization /
extension_header), CRLF
]
@ -499,6 +504,68 @@ PP.PPCompositeParser subclass: SIPGrammar [
(STAR / (self contact_param, (COMMA, self contact_param) star))
]
Authorization [
<category: 'WWW-Authenticate'>
^'Authorization' asParser, HCOLON, self credentials
]
credentials [
<category: 'WWW-Authenticate'>
^('Digest' asParser, LWS, self digest_response) / self other_response
]
digest_response [
<category: 'WWW-Authenticate'>
^self dig_resp, (COMMA, self dig_resp) star
]
dig_resp [
<category: 'WWW-Authenticate'>
^self username / self realm / self nonce / self digest_uri /
self dresponse / self algorithm / self cnonce / self opaque /
self message_qop / self nonce_count / self auth_param
]
username [
<category: 'WWW-Authenticate'>
^'username' asParser, EQUAL, self quoted_string
]
digest_uri [
<category: 'WWW-Authenticate'>
^'uri' asParser, EQUAL, LDQUOT, self digest_uri_value, RDQUOT
]
digest_uri_value [
<category: 'WWW-Authenticate'>
^RequestURI
]
message_qop [
<category: 'WWW-Authenticate'>
^'qop' asParser, EQUAL, self qop_value
]
cnonce [
<category: 'WWW-Authenticate'>
^'cnonce' asParser / EQUAL / self nonce_value
]
nonce_count [
<category: 'WWW-Authenticate'>
^'nc' asParser, EQUAL, (self LHEX min: 8 max: 8) flatten
]
dresponse [
<category: 'WWW-Authenticate'>
^'response' asParser , EQUAL , self request_digest
]
request_digest [
<category: 'WWW-Authenticate'>
^LDQUOT, (self LHEX min: 32 max: 32) flatten, RDQUOT
]
WWWAuthenticate [
<category: 'WWW-Authenticate'>
^'WWW-Authenticate' asParser, HCOLON, self challenge
@ -583,6 +650,11 @@ PP.PPCompositeParser subclass: SIPGrammar [
^self token
]
other_response [
<category: 'WWW-Authenticate'>
^self auth_scheme, LWS, self auth_param, (COMMA, self auth_param) plus
]
auth_scheme [
<category: 'WWW-Authenticate'>
^self token

View File

@ -331,4 +331,11 @@ PP.PPCompositeParserTest subclass: SIPGrammarTest [
res := self parse: data asString.
]
testAuthorization [
| res |
res := SIPGrammar new Authorization parse: 'Authorization: Digest username="st", realm="Yate", nonce="373ef30b297545cbce99fad09f1409cb.1392124197", uri="sip:127.0.0.1", algorithm=MD5, response="bc8dfaa413e897863dbab4c622e4b9b4"'.
self assert: res first equals: 'Authorization'.
self assert: res third size equals: 3.
]
]