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

mgcp: Be able to parse the X-Osmux extension we have

This commit is contained in:
Holger Hans Peter Freyther 2014-08-26 19:04:52 +02:00
parent 0ffe0afcb5
commit d5248eceec
2 changed files with 20 additions and 1 deletions

View File

@ -379,10 +379,28 @@ PP.PPCompositeParserTest subclass: MGCPParserTest [
]
exampleCRCXWithOsmux [
^String streamContents: [:stream |
stream
nextPutAll: 'CRCX 361562151 1@mgw MGCP 1.0'; nl;
nextPutAll: 'X-Osmux: on'; cr; nl;
nextPutAll: 'C: f553fcb979'; cr; nl;
nextPutAll: 'L: p:20, a:AMR, nt:IN'; cr; nl;
nextPutAll: 'M: recvonly'; cr; nl
]
]
parserClass [
^MGCPParser
]
testParseCRCXWithOsmux [
| crcx |
crcx := self parse: self exampleCRCXWithOsmux.
self assert: crcx class verb equals: 'CRCX'.
]
testParseCRCX [
| crcx |
crcx := self parse: self class crcxMessage.

View File

@ -130,7 +130,8 @@ PP.PPCompositeParser subclass: MGCPGrammar [
('ES' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('PL' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('MD' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('X-Osmo-CP' asParser, $: asParser, #blank asParser star, self wordParser star flatten)
('X-Osmo-CP' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('X-Osmux' asParser, $: asParser, #blank asParser star, self wordParser star flatten)
]
MGCPResponse [