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

sip: Initial version of the Grammar capable of parsing a response

There is still an issue with the white space handling in the
message header.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-11 20:30:15 +02:00
commit afa0ae4c95
6 changed files with 15416 additions and 0 deletions

1
.gitignore vendored Normal file
View File

@ -0,0 +1 @@
*.sw?

15067
docs/RFC3261.txt Normal file

File diff suppressed because it is too large Load Diff

29
example/invite Normal file
View File

@ -0,0 +1,29 @@
INVITE sip:9198@172.18.1.72 SIP/2.0
Via: SIP/2.0/UDP 172.16.254.24;rport;branch=z9hG4bKrebupeuh
Max-Forwards: 70
To: <sip:9198@172.18.1.72>
From: "zecke" <sip:1000@sysmocom.de>;tag=wmycl
Call-ID: ofcwnpmulmceasg@xiaoyu
CSeq: 982 INVITE
Contact: <sip:1000@172.18.254.25>
Content-Type: application/sdp
Allow: INVITE,ACK,BYE,CANCEL,OPTIONS,PRACK,REFER,NOTIFY,SUBSCRIBE,INFO,MESSAGE
Supported: replaces,norefersub,100rel
User-Agent: Twinkle/1.4.2
Content-Length: 310
v=0
o=twinkle 2038576622 441641029 IN IP4 172.18.254.24
s=-
c=IN IP4 172.18.254.24
t=0 0
m=audio 8000 RTP/AVP 98 97 8 0 3 101
a=rtpmap:98 speex/16000
a=rtpmap:97 speex/8000
a=rtpmap:8 PCMA/8000
a=rtpmap:0 PCMU/8000
a=rtpmap:3 GSM/8000
a=rtpmap:101 telephone-event/8000
a=fmtp:101 0-15
a=ptime:20

29
example/invite2 Normal file
View File

@ -0,0 +1,29 @@
INVITE sip:9198@172.18.1.72 SIP/2.0
Via: SIP/2.0/UDP 172.18.254.24;rport;branch=z9hG4bKrebupeuh
Max-Forwards: 70
To: <sip:119198@172.18.1.72>
From: "zecke" <sip:1000@secretlabs.de>;tag=wmycl
Call-ID: ofcwnpmulmceasg@xiaoyu
CSeq: 982 INVITE
Contact: <sip:1000@172.18.254.25>
Content-Type: application/sdp
Allow: INVITE,ACK,BYE,CANCEL,OPTIONS,PRACK,REFER,NOTIFY,SUBSCRIBE,INFO,MESSAGE
Supported: replaces,norefersub,100rel
User-Agent: Twinkle/1.4.2
Content-Length: 310
v=0
o=twinkle 2038576622 441641029 IN IP4 172.18.254.25
s=-
c=IN IP4 172.18.254.25
t=0 0
m=audio 8000 RTP/AVP 98 97 8 0 3 101
a=rtpmap:98 speex/16000
a=rtpmap:97 speex/8000
a=rtpmap:8 PCMA/8000
a=rtpmap:0 PCMU/8000
a=rtpmap:3 GSM/8000
a=rtpmap:101 telephone-event/8000
a=fmtp:101 0-15
a=ptime:20

183
grammar/SIPGrammar.st Normal file
View File

@ -0,0 +1,183 @@
"
(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/>.
"
PackageLoader fileInPackage: 'PetitParser'.
PP.PPCompositeParser subclass: SIPGrammar [
| Response StatusLine message_header
CRLF SP HTAB HCOLON SWS LWS WSP
message_body SIPVersion StatusCode ReasonPhrase
extension_header header_name header_value |
"http://sofia-sip.org/repos/sofia-sip/libsofia-sip-ua/sip/GRAMMAR"
<category: 'SIP-Core'>
<comment: 'I try to parse RFC3261'>
start [
<category: 'start'>
^ Response
]
CRLF [
<category: 'misc'>
^ Character cr asParser, Character nl asParser
]
SP [
<category: 'misc'>
^ $ asParser
]
Response [
<category: 'response'>
^ StatusLine, message_header star, CRLF, message_body optional
]
StatusLine [
<category: 'response'>
^ SIPVersion, SP, StatusCode, SP, ReasonPhrase, CRLF
]
SIPVersion [
<category: 'generic'>
^ 'SIP/' asParser, #digit asParser, $. asParser, #digit asParser
]
StatusCode [
<category: 'response'>
"Combined into one..."
^ '100' asParser / "Trying"
'180' asParser / "Ringing"
'181' asParser / "Call Is Being Forwarded"
'182' asParser / "Queued"
'183' asParser / "Session Progress"
'200' asParser / "OK"
'300' asParser / "Multiple Choices"
'301' asParser / "Moved Permanently"
'302' asParser / "Moved Temporarily"
'380' asParser / "Alternative Service"
'400' asParser / "Bad Request"
'401' asParser / "Unauthorized"
'402' asParser / "Payment Required"
'403' asParser / "Forbidden"
'404' asParser / "Not Found"
'405' asParser / "Method Not Allowed"
'406' asParser / "Not Acceptable"
'407' asParser / "Proxy Authentication Required"
'408' asParser / "Request Timeout"
'410' asParser / "Gone"
'413' asParser / "Request Entity Too Large"
'414' asParser / "Request-URI Too Large"
'415' asParser / "Unsupported Media Type"
'416' asParser / "Unsupported URI Scheme"
'420' asParser / "Bad Extension"
'421' asParser / "Extension Required"
'423' asParser / "Interval Too Brief"
'480' asParser / "Temporarily not available"
'481' asParser / "Call Leg/Transaction Does Not Exist"
'482' asParser / "Loop Detected"
'483' asParser / "Too Many Hops"
'484' asParser / "Address Incomplete"
'485' asParser / "Ambiguous"
'486' asParser / "Busy Here"
'487' asParser / "Request Terminated"
'488' asParser / "Not Acceptable Here"
'491' asParser / "Request Pending"
'493' asParser / "Undecipherable"
'500' asParser / "Internal Server Error"
'501' asParser / "Not Implemented"
'502' asParser / "Bad Gateway"
'503' asParser / "Service Unavailable"
'504' asParser / "Server Time-out"
'505' asParser / "SIP Version not supported"
'513' asParser / "Message Too Large"
'600' asParser / "Busy Everywhere"
'603' asParser /"Decline"
'604' asParser /"Does not exist anywhere"
'606' asParser "Not Acceptable"
]
ReasonPhrase [
<category: 'response'>
^ (#digit asParser / Character space asParser / HTAB / #letter asParser) star flatten
]
message_header [
"Simplified..."
<category: 'generic'>
^ (extension_header), CRLF
]
message_body [
^ #any asParser plus flatten
]
extension_header [
<category: 'generic'>
^ header_name, HCOLON, header_value
]
header_name [
<category: 'generic'>
"hmm 1*() should be optional but it must be star here"
^ (#letter asParser / #digit asParser /
$- asParser / $. asParser /
$! asParser / $% asParser /
$* asParser / $_ asParser /
$+ asParser / $` asParser /
$' asParser / $~ asParser) star flatten
]
header_value [
<category: 'generic'>
"TODO: TEXT-UTF8char / UTF8-CONT"
^ (#letter asParser / #digit asParser / #punctuation asParser / #blank asParser / LWS) star flatten
]
HTAB [
<category: 'generic'>
^ Character tab asParser
]
HCOLON [
<category: 'generic'>
^ (SP / HTAB) star, $: asParser, SWS
]
WSP [
<category: 'misc'>
^ #blank asParser
]
LWS [
<category: 'generic'>
(WSP star, CRLF) optional, WSP plus
]
SWS [
<category: 'generic'>
^ LWS optional
]
]

107
grammar/SIPGrammarTest.st Normal file
View File

@ -0,0 +1,107 @@
"
(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/>.
"
PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: SIPGrammarTest [
<comment: 'I try to parse some SIP messages.'>
<category: 'SIP-Core'>
SIPGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('SIPGrammar')
]
parserClass [
<category: 'accessing'>
^ SIPGrammar
]
testTrying [
| data res hdr |
data := #(16r53 16r49 16r50 16r2F 16r32 16r2E 16r30 16r20
16r31 16r30 16r30 16r20 16r54 16r72 16r79 16r69
16r6E 16r67 16r0D 16r0A 16r56 16r69 16r61 16r3A
16r20 16r53 16r49 16r50 16r2F 16r32 16r2E 16r30
16r2F 16r55 16r44 16r50 16r20 16r31 16r37 16r32
16r2E 16r31 16r36 16r2E 16r32 16r35 16r34 16r2E
16r32 16r34 16r3B 16r72 16r70 16r6F 16r72 16r74
16r3D 16r35 16r30 16r36 16r30 16r3B 16r62 16r72
16r61 16r6E 16r63 16r68 16r3D 16r7A 16r39 16r68
16r47 16r34 16r62 16r4B 16r66 16r77 16r6A 16r6C
16r78 16r64 16r72 16r76 16r0D 16r0A 16r46 16r72
16r6F 16r6D 16r3A 16r20 16r22 16r7A 16r65 16r63
16r6B 16r65 16r22 16r20 16r3C 16r73 16r69 16r70
16r3A 16r31 16r30 16r30 16r30 16r40 16r6F 16r6E
16r2D 16r77 16r61 16r76 16r65 16r73 16r2E 16r63
16r6F 16r6D 16r3E 16r3B 16r74 16r61 16r67 16r3D
16r77 16r6D 16r79 16r63 16r6C 16r0D 16r0A 16r54
16r6F 16r3A 16r20 16r3C 16r73 16r69 16r70 16r3A
16r39 16r31 16r39 16r38 16r40 16r31 16r37 16r32
16r2E 16r31 16r36 16r2E 16r31 16r2E 16r37 16r32
16r3E 16r0D 16r0A 16r43 16r61 16r6C 16r6C 16r2D
16r49 16r44 16r3A 16r20 16r6F 16r66 16r63 16r77
16r6E 16r70 16r6D 16r75 16r6C 16r6D 16r63 16r65
16r61 16r73 16r67 16r40 16r78 16r69 16r61 16r6F
16r79 16r75 16r0D 16r0A 16r43 16r53 16r65 16r71
16r3A 16r20 16r39 16r38 16r33 16r20 16r49 16r4E
16r56 16r49 16r54 16r45 16r0D 16r0A 16r55 16r73
16r65 16r72 16r2D 16r41 16r67 16r65 16r6E 16r74
16r3A 16r20 16r46 16r72 16r65 16r65 16r53 16r57
16r49 16r54 16r43 16r48 16r2D 16r6D 16r6F 16r64
16r5F 16r73 16r6F 16r66 16r69 16r61 16r2F 16r31
16r2E 16r30 16r2E 16r68 16r65 16r61 16r64 16r2D
16r67 16r69 16r74 16r2D 16r64 16r66 16r66 16r34
16r31 16r61 16r66 16r20 16r32 16r30 16r31 16r31
16r2D 16r30 16r34 16r2D 16r32 16r30 16r20 16r31
16r34 16r2D 16r31 16r31 16r2D 16r32 16r34 16r20
16r2B 16r30 16r32 16r30 16r30 16r0D 16r0A 16r43
16r6F 16r6E 16r74 16r65 16r6E 16r74 16r2D 16r4C
16r65 16r6E 16r67 16r74 16r68 16r3A 16r20 16r30
16r0D 16r0A 16r0D 16r0A) asByteArray.
res := self parse: data asString.
self assert: res size = 4.
self assert: res first third = '100'.
self assert: (res first at: 5) = 'Trying'.
hdr := res second.
self assert: (hdr at: 1) first first = 'Via'.
self assert: (hdr at: 1) first third = ' 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: 3) first first = 'To'.
self assert: (hdr at: 3) first third = ' <sip:9198@172.16.1.72>'.
self assert: (hdr at: 4) first first = 'Call-ID'.
self assert: (hdr at: 4) first third = ' ofcwnpmulmceasg@xiaoyu'.
self assert: (hdr at: 5) first first = 'CSeq'.
self assert: (hdr at: 5) first third = ' 983 INVITE'.
self assert: (hdr at: 6) first first = 'User-Agent'.
self assert: (hdr at: 6) first third = ' FreeSWITCH-mod_sofia/1.0.head-git-dff41af 2011-04-20 14-11-24 +0200'.
self assert: (hdr at: 7) first first = 'Content-Length'.
self assert: (hdr at: 7) first third = ' 0'.
]
]