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

command: Be able to parse a MGCP Command

The Command and Response code could and should share parts. Start
with slowly aligning the APIs and begin being able to parse a
command from a string.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-28 18:21:14 +02:00
parent be46bf5b35
commit f0549c2df8
3 changed files with 87 additions and 23 deletions

View File

@ -16,27 +16,45 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: MGCPCommand [
Object subclass: MGCPCommandBase [
| transaction endp params sdp |
<comment: 'I am a command send to a MGCP gateway. I know my timeout
and such. Each MGCPGateWay can have a MGCPCommand subclass to specify
certain things. E.g. the endpoint numbering is different'>
<category: 'OsmoMGCP-callagent'>
MGCPCommand class >> create: anEndpoint callId: aCallId [
^ (self new)
endpoint: anEndpoint;
parameterAdd: 'C: ', aCallId asString;
MGCPCommandBase class >> fromDict: nodes [
| verb |
verb := nodes first.
self allSubclassesDo: [:each |
each verb = verb
ifTrue: [^each parseFromDict: nodes]].
^self error: 'Unknown command verb "%1"' % {verb}.
]
MGCPCommandBase class >> parseFromDict: nodes [
^self new
transactionId: nodes third;
endpoint: (nodes at: 5);
addParametersInternal: (nodes at: 9);
sdp: (nodes at: 10);
yourself
]
MGCPCommand class >> create: anEndpoint [
MGCPCommandBase class >> create: anEndpoint callId: aCallId [
^ (self new)
endpoint: anEndpoint;
addParameter: 'C' with: aCallId asString;
yourself
]
MGCPCommandBase class >> create: anEndpoint [
^ (self new)
endpoint: anEndpoint;
yourself
]
MGCPCommand class >> verb [
MGCPCommandBase class >> verb [
<category: 'verb'>
^ self subclassResponsibility
]
@ -53,7 +71,29 @@ Object subclass: MGCPCommand [
parameterAdd: aParam [
<category: 'private'>
self params add: aParam.
^self error: 'This is deprecated. Use >>#addParameter:with:'
]
addParameter: aKey with: aValue [
^self params add: aKey->aValue.
]
addParametersInternal: anArray [
<category: 'private'>
"TODO: Share code with MGCPResponse"
anArray do: [:each |
self addParameter: each first first asString with: each first fourth].
]
parameterAt: aKey [
^self parameterAt: aKey ifAbsent: [^self error: 'Parameter not found'].
]
parameterAt: aKey ifAbsent: aBlock [
self params do: [:each |
each key = aKey
ifTrue: [^each value]].
^aBlock value.
]
params [
@ -85,7 +125,9 @@ Object subclass: MGCPCommand [
"write the parameters"
self params do: [:each |
out
nextPutAll: each;
nextPutAll: each key;
nextPutAll: ': ';
nextPutAll: each value;
cr; nl.
].
@ -100,7 +142,7 @@ Object subclass: MGCPCommand [
]
]
MGCPCommand subclass: MGCPCRCXCommand [
MGCPCommandBase subclass: MGCPCRCXCommand [
<comment: 'I represent a CRCX message'>
<category: 'OsmoMGCP-Callagent'>
@ -118,7 +160,7 @@ MGCPCommand subclass: MGCPCRCXCommand [
]
]
MGCPCommand subclass: MGCPMDCXCommand [
MGCPCommandBase subclass: MGCPMDCXCommand [
<comment: 'I represent a MDCX message'>
<category: 'OsmoMGCP-Callagent'>
@ -135,7 +177,7 @@ MGCPCommand subclass: MGCPMDCXCommand [
]
]
MGCPCommand subclass: MGCPDLCXCommand [
MGCPCommandBase subclass: MGCPDLCXCommand [
<comment: 'I represent a DLCX message'>
<category: 'OsmoMGCP-Callagent'>
@ -150,7 +192,7 @@ MGCPCommand subclass: MGCPDLCXCommand [
]
]
MGCPCommand subclass: MGCPAUEPComamnd [
MGCPCommandBase subclass: MGCPAUEPComamnd [
<comment: 'I represent an AUEP message'>
<category: 'OsmoMGCP-Callagent'>
@ -165,7 +207,7 @@ MGCPCommand subclass: MGCPAUEPComamnd [
]
]
MGCPCommand subclass: MGCPOsmoRSIPCommand [
MGCPCommandBase subclass: MGCPOsmoRSIPCommand [
<comment: 'I represent an Osmocom Extension to MGCP to reset remote
mediagateways. The spec is working the other way around.'>
<category: 'OsmoMGCP-Callagent'>

View File

@ -27,11 +27,15 @@ MGCPGrammar subclass: MGCPParser [
MGCPCommand [
<category: 'extract'>
^ super MGCPCommand => [:nodes | nil]
^ super MGCPCommand => [:nodes | MGCPCommandBase fromDict: nodes]
]
MGCPResponse [
<category: 'extract'>
^ super MGCPResponse => [:nodes | MGCPResponse fromDict: nodes]
]
endpointName [
^super endpointName flatten
]
]

View File

@ -78,8 +78,8 @@ TestCase subclass: MGCPCommandTest [
trans := MGCPTransaction on: self endpoint of: self callagent.
trans transactionId: '808080'.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: recvonly';
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
@ -130,8 +130,8 @@ TestCase subclass: MGCPCommandTest [
trans := MGCPTransaction on: self endpoint of: self callagent.
trans transactionId: '808080'.
mdcx := (MGCPMDCXCommand createMDCX: self endpoint callId: '4a84ad5d25f')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: recvonly';
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
sdp: self exampleSDP;
yourself.
trans command: mdcx.
@ -224,8 +224,8 @@ TestCase subclass: MGCPTransactionTest [
trans := MGCPShortTransaction on: self endpoint of: self timeoutCallagent.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: recvonly';
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
@ -248,8 +248,8 @@ TestCase subclass: MGCPTransactionTest [
trans := MGCPShortTransaction on: self endpoint of: self dropAgent.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: recvonly';
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
@ -352,10 +352,28 @@ TestCase subclass: MGCPEndpointAllocTest [
PP.PPCompositeParserTest subclass: MGCPParserTest [
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPParserTest class >> crcxMessage [
^String streamContents: [:stream |
stream
nextPutAll: 'CRCX 1 14@mgw MGCP 1.0'; cr; nl;
nextPutAll: 'C: 4a84ad5d25f'; cr; nl;
nextPutAll: 'L: p:20, a:GSM-EFR, nt:IN'; cr; nl;
nextPutAll: 'M: recvonly'; cr; nl]
]
parserClass [
^MGCPParser
]
testParseCRCX [
| crcx |
crcx := self parse: self class crcxMessage.
self assert: crcx class verb equals: 'CRCX'.
self assert: (crcx parameterAt: 'M') equals: 'recvonly'.
self assert: crcx asDatagram equals: self class crcxMessage.
]
testRespParse [
| nl res sdp |
nl := Character cr asString, Character nl asString.