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

mgcp: Add first bits for the MGCP Grammar using PetitParser

This commit is contained in:
Holger Hans Peter Freyther 2010-09-02 23:44:55 +08:00
parent 2308eb88f4
commit 6514c5c7f7
2 changed files with 116 additions and 0 deletions

80
MGCPGrammar.st Normal file
View File

@ -0,0 +1,80 @@
"
Do not copy...
"
PackageLoader fileInPackage: 'PetitParser'.
PP.PPCompositeParser subclass: MGCPGrammar [
| MGCPMessage EOL One_WSP MGCPMessage MGCPCommandLine MGCPVerb transaction_id endpointName MGCPversion MGCPCommand |
<category: 'MGCP-Core'>
<comment: 'I am a the Grammar of the Media Gateway Control Protocol'>
"'Implement MGCPResponse'"
start [
<category: 'accessing'>
^ MGCPMessage
]
EOL [
<category: 'grammar-common'>
^ #newline asParser plus
]
One_WSP [
<category: 'grammar-common'>
^ #blank asParser plus
]
MGCPMessage [
<category: 'grammar-common'>
^ MGCPCommand "/ MGCPResponse"
]
MGCPCommandLine [
<category: 'grammar-cmd'>
^ self MGCPVerb,
self One_WSP,
self transaction_id,
self One_WSP,
self endpointName,
self One_WSP,
self MGCPversion,
self EOL
]
MGCPVerb [
<category: 'grammar-cmd'>
^ 'EPCF' asParser /
'CRCX' asParser /
'MDCX' asParser /
'DLCX' asParser /
'RQNT' asParser /
'NTFY' asParser /
'AUEP' asParser /
'AUCX' asParser /
'RSIP' asParser
]
transaction_id [
<category: 'grammar-cmd'>
^ ((#digit asParser) min: 1 max: 9) flatten
]
endpointName [
<category: 'grammar-cmd'>
"simplified version"
^ #word asParser star flatten, $@ asParser, #word asParser star flatten
]
MGCPversion [
<category: 'grammar-cmd'>
"skipping the optional profilename for now"
^ 'MGCP' asParser, One_WSP, #digit asParser, $. asParser, #digit asParser
]
MGCPCommand [
<category: 'grammar-cmd'>
^ MGCPCommandLine
]
]

36
MGCPGrammarTest.st Normal file
View File

@ -0,0 +1,36 @@
"
Do not copy...
"
PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: MGCPGrammarTest [
<comment: 'I test some parts of thegrammar'>
<category: 'MGCP-Tests'>
MGCPGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>
^#('MGCPGrammar')
]
parserClass [
<category: 'accessing'>
^MGCPGrammar
]
testCommand [
<category: 'test-command'>
| res |
res := self parse: 'AUEP 23444 13@mgw MGCP 1.0',
Character cr asString, Character lf asString.
self assert: res size = 8.
self assert: (res at: 1) = 'AUEP'.
self assert: (res at: 3) = 23444.
self assert: (res at: 5) = #('23' $@ 'mgw').
res inspect.
]
]