aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-08-26 19:04:52 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-08-26 19:04:52 +0200
commitd5248eceecd9d2f8c7061538163bc8ec80168dfc (patch)
tree4c720e44c09c454a93159b8868d0b50eb65aed87
parent0ffe0afcb511d3abb2c0dda69c15f2b1bf74c770 (diff)
mgcp: Be able to parse the X-Osmux extension we have
-rw-r--r--callagent/Tests.st18
-rw-r--r--grammar/MGCPGrammar.st3
2 files changed, 20 insertions, 1 deletions
diff --git a/callagent/Tests.st b/callagent/Tests.st
index 918ec45..a0f42a4 100644
--- a/callagent/Tests.st
+++ b/callagent/Tests.st
@@ -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.
diff --git a/grammar/MGCPGrammar.st b/grammar/MGCPGrammar.st
index dcde4e2..2986273 100644
--- a/grammar/MGCPGrammar.st
+++ b/grammar/MGCPGrammar.st
@@ -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 [