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

grammar: Parse the To/From header according to the grammar

Right now the UTF8 support for the displayname is still
missing and needs to be added later. The to_spec is not
part of the RFC but it makes our code more happy if things
look like the from_spec.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-29 17:25:30 +02:00
parent c386b9f147
commit ed42decd4a
2 changed files with 101 additions and 6 deletions

View File

@ -21,6 +21,7 @@ PackageLoader fileInPackage: 'PetitParser'.
PP.PPCompositeParser subclass: SIPGrammar [
| Response StatusLine message_header
CRLF SP HTAB HCOLON SWS LWS WSP COMMA SEMI SLASH COLON EQUAL
LAQUOT RAQUOT DQUOTE
message_body SIPVersion StatusCode ReasonPhrase
extension_header header_name header_value
Request RequestLine Method extension_method
@ -57,7 +58,8 @@ PP.PPCompositeParser subclass: SIPGrammar [
RequestURI [
<category: 'request'>
^ self SIPURI / self SIPSURI
"TODO: absoluteURI is not supported"
^ self SIPURI / self SIPSURI "/ self absoluteURI"
]
SIPURI [
@ -302,7 +304,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
"Simplified..."
<category: 'generic'>
^ (self Via / self CSeq / extension_header), CRLF
^ (self Via / self CSeq / self From / self To /extension_header), CRLF
]
message_body [
@ -376,8 +378,34 @@ PP.PPCompositeParser subclass: SIPGrammar [
gen_value [
<category: 'generic'>
"TODO: quoted string not ported"
^ self token / self host "/ self quoted_string"
^ self token / self host / self quoted_string
]
quoted_string [
<category: 'generic'>
^ self SWS, DQUOTE, (self qdtext / self quoted_pair) star, DQUOTE
]
qdtext [
| str |
<category: 'generic'>
"TODO: UTF-8 text is not working properly..."
str := WriteStream on: (String new).
str nextPut: (Character value: 16r21).
16r23 to: 16r5B do: [:each | str nextPut: (Character value: each)].
16r5D to: 16r7E do: [:each | str nextPut: (Character value: each)].
^ SWS / (PP.PPPredicateObjectParser chars: str contents message: 'qdtext') "/ UTF8_NONASCII"
]
quoted_pair [
| str |
<category: 'generic'>
str := WriteStream on: (String new).
str nextPut: (Character value: 16r21).
16r00 to: 16r09 do: [:each | str nextPut: (Character value: each)].
16r0B to: 16r0C do: [:each | str nextPut: (Character value: each)].
16r5D to: 16r7E do: [:each | str nextPut: (Character value: each)].
^ '\' asParser, (PP.PPPredicateObjectParser chars: str contents message: 'quoted_pair')
]
sent_protocol [
@ -411,6 +439,58 @@ PP.PPCompositeParser subclass: SIPGrammar [
^ self token
]
From [
<category: 'from'>
^ ('From' asParser / 'f' asParser), HCOLON, self from_spec
]
from_spec [
<category: 'from'>
^ (self name_addr / self addr_spec), (SEMI, self from_param) star
]
from_param [
<category: 'from'>
^ self tag_param / self generic_param
]
To [
<category: 'to'>
^ ('To' asParser / $t asParser), HCOLON, self to_spec
]
to_spec [
"I do not exist in the RFC but I make things more beautiful and
symmetric with the From case"
<category: 'to'>
^ (self name_addr / self addr_spec), (SEMI, self to_param) star
]
to_param [
<category: 'to'>
^ self tag_param / self generic_param
]
tag_param [
<category: 'to'>
^ 'tag' asParser, EQUAL, self token
]
name_addr [
<category: 'to-from'>
^ self display_name optional, LAQUOT, self addr_spec, self RAQUOT
]
display_name [
^ (self token, LWS) star / self quoted_string
]
addr_spec [
<category: 'to-from'>
"TODO: absoluteURI is not supported"
^ self SIPURI / self SIPSURI "/ self absoluteURI"
]
extension_header [
<category: 'generic'>
^ header_name, HCOLON, header_value
@ -489,4 +569,19 @@ PP.PPCompositeParser subclass: SIPGrammar [
<category: 'generic'>
^ LWS optional
]
LAQUOT [
<category: 'generic'>
^ SWS, $< asParser
]
RAQUOT [
<category: 'generic'>
^ $> asParser, SWS
]
DQUOTE [
<category: 'generic'>
^ $" asParser
]
]

View File

@ -87,10 +87,10 @@ PP.PPCompositeParserTest subclass: SIPGrammarTest [
self assert: (hdr at: 1) first third asFoldedString = 'SIP/2.0/UDP 172.16.254.24;rport=5060;branch=z9hG4bKfwjlxdrv'.
self assert: (hdr at: 2) first first = 'From'.
self assert: (hdr at: 2) first third = '"zecke" <sip:1000@on-waves.com>;tag=wmycl'.
self assert: (hdr at: 2) first third asFoldedString = '"zecke" <sip:1000@on-waves.com>;tag=wmycl'.
self assert: (hdr at: 3) first first = 'To'.
self assert: (hdr at: 3) first third = '<sip:9198@172.16.1.72>'.
self assert: (hdr at: 3) first third asFoldedString = '<sip:9198@172.16.1.72>'.
self assert: (hdr at: 4) first first = 'Call-ID'.
self assert: (hdr at: 4) first third = 'ofcwnpmulmceasg@xiaoyu'.