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

parser/grammar: Be able to parse domain used by Yate.

It looks like "domain" is not proper in yate. Just parse it as
numbers and words.
This commit is contained in:
Holger Hans Peter Freyther 2014-06-02 21:55:27 +02:00
parent 24dbbc986c
commit 8b626c8a52
3 changed files with 35 additions and 1 deletions

View File

@ -57,6 +57,10 @@ SIPGrammar subclass: SIPParser [
^ super SIPSURI => [:nodes | self class combineUri: nodes] ^ super SIPSURI => [:nodes | self class combineUri: nodes]
] ]
URI [
^super URI flatten
]
via_ttl [ via_ttl [
<category: 'via'> <category: 'via'>
^ super via_ttl => [:nodes | SIPGenericParam fromMandatory: nodes] ^ super via_ttl => [:nodes | SIPGenericParam fromMandatory: nodes]

View File

@ -20,6 +20,22 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
<category: 'OsmoSIP-Parser-Tests'> <category: 'OsmoSIP-Parser-Tests'>
<comment: 'I excercise the SIPParser a bit'> <comment: 'I excercise the SIPParser a bit'>
SIPParserTest class >> exampleYateBye [
^String streamContents: [:stream |
stream
nextPutAll: 'SIP/2.0 401 Unauthorized'; cr; nl;
nextPutAll: 'Via: SIP/2.0/UDP 0.0.0.0:5061;branch=z9hG4bKMzU3OTE4OTQ0Niw5NjM5Nw__;rport=5061;received=1.2.3.4'; cr; nl;
nextPutAll: 'From: <sip:0503@1.2.3.4>;tag=MzU3OTE5NjYzOTMyODExMDEwOTE_'; cr; nl;
nextPutAll: 'To: <sip:+1234@4.3.2.1>;tag=1176641923'; cr; nl;
nextPutAll: 'Call-ID: NTQ5MzM3NzA4@xiaoyu'; cr; nl;
nextPutAll: 'CSeq: 2 BYE'; cr; nl;
nextPutAll: 'WWW-Authenticate: Digest realm="Yate", domain="1.2.3.4", nonce="b787f1fbc9a864af6975d9f59ac49ef1.1401736687", stale=FALSE, algorithm=MD5'; cr; nl;
nextPutAll: 'Server: YATE/4.3.0'; cr; nl;
nextPutAll: 'Allow: ACK, INVITE, BYE, CANCEL, REGISTER, REFER, OPTIONS, INFO'; cr; nl;
nextPutAll: 'Content-Length: 0'; cr; nl;
cr; nl]
]
parserClass [ parserClass [
<category: 'accessing'> <category: 'accessing'>
^ SIPParser ^ SIPParser
@ -228,4 +244,11 @@ PP.PPCompositeParserTest subclass: SIPParserTest [
self assert: auth uri equals: 'sip:127.0.0.1'. self assert: auth uri equals: 'sip:127.0.0.1'.
self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'. self assert: auth response equals: 'bc8dfaa413e897863dbab4c622e4b9b4'.
] ]
testYateBye [
| res |
res := self parse: self class exampleYateBye.
"Just check it can be parsed."
]
] ]

View File

@ -19,7 +19,7 @@
PP.PPCompositeParser subclass: SIPGrammar [ PP.PPCompositeParser subclass: SIPGrammar [
| Response StatusLine message_header | Response StatusLine message_header
CRLF SP HTAB HCOLON SWS LWS WSP COMMA SEMI SLASH COLON EQUAL CRLF SP HTAB HCOLON SWS LWS WSP COMMA SEMI SLASH COLON EQUAL
LAQUOT RAQUOT LDQUOT RDQUOT DQUOTE STAR LAQUOT RAQUOT LDQUOT RDQUOT DQUOTE STAR URI
message_body SIPVersion StatusCode ReasonPhrase message_body SIPVersion StatusCode ReasonPhrase
extension_header header_name header_value extension_header header_name header_value
Request RequestLine Method extension_method Request RequestLine Method extension_method
@ -44,6 +44,13 @@ PP.PPCompositeParser subclass: SIPGrammar [
^ $ asParser ^ $ asParser
] ]
URI [
"TODO: URI should be parsed properly but yate seems to already
violate the RFC"
^(#digit asParser / #word asParser) star
"^absoluteURI / abs-path"
]
Request [ Request [
<category: 'request'> <category: 'request'>
^ RequestLine, message_header star, CRLF, message_body optional ^ RequestLine, message_header star, CRLF, message_body optional