From f0549c2df8860aee6887b8c9426701ddb5d67cb2 Mon Sep 17 00:00:00 2001 From: Holger Hans Peter Freyther Date: Wed, 28 May 2014 18:21:14 +0200 Subject: [PATCH] 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. --- callagent/MGCPCommands.st | 70 +++++++++++++++++++++++++++++++-------- callagent/MGCPParser.st | 6 +++- callagent/Tests.st | 34 ++++++++++++++----- 3 files changed, 87 insertions(+), 23 deletions(-) diff --git a/callagent/MGCPCommands.st b/callagent/MGCPCommands.st index 91c9fe7..1e316f0 100644 --- a/callagent/MGCPCommands.st +++ b/callagent/MGCPCommands.st @@ -16,27 +16,45 @@ along with this program. If not, see . " -Object subclass: MGCPCommand [ +Object subclass: MGCPCommandBase [ | transaction endp params sdp | - 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 [ ^ self subclassResponsibility ] @@ -53,7 +71,29 @@ Object subclass: MGCPCommand [ parameterAdd: aParam [ - self params add: aParam. + ^self error: 'This is deprecated. Use >>#addParameter:with:' + ] + + addParameter: aKey with: aValue [ + ^self params add: aKey->aValue. + ] + + addParametersInternal: anArray [ + + "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 [ @@ -118,7 +160,7 @@ MGCPCommand subclass: MGCPCRCXCommand [ ] ] -MGCPCommand subclass: MGCPMDCXCommand [ +MGCPCommandBase subclass: MGCPMDCXCommand [ @@ -135,7 +177,7 @@ MGCPCommand subclass: MGCPMDCXCommand [ ] ] -MGCPCommand subclass: MGCPDLCXCommand [ +MGCPCommandBase subclass: MGCPDLCXCommand [ @@ -150,7 +192,7 @@ MGCPCommand subclass: MGCPDLCXCommand [ ] ] -MGCPCommand subclass: MGCPAUEPComamnd [ +MGCPCommandBase subclass: MGCPAUEPComamnd [ @@ -165,7 +207,7 @@ MGCPCommand subclass: MGCPAUEPComamnd [ ] ] -MGCPCommand subclass: MGCPOsmoRSIPCommand [ +MGCPCommandBase subclass: MGCPOsmoRSIPCommand [ diff --git a/callagent/MGCPParser.st b/callagent/MGCPParser.st index a052f55..f05041e 100644 --- a/callagent/MGCPParser.st +++ b/callagent/MGCPParser.st @@ -27,11 +27,15 @@ MGCPGrammar subclass: MGCPParser [ MGCPCommand [ - ^ super MGCPCommand => [:nodes | nil] + ^ super MGCPCommand => [:nodes | MGCPCommandBase fromDict: nodes] ] MGCPResponse [ ^ super MGCPResponse => [:nodes | MGCPResponse fromDict: nodes] ] + + endpointName [ + ^super endpointName flatten + ] ] diff --git a/callagent/Tests.st b/callagent/Tests.st index d9ce38b..4ec2175 100644 --- a/callagent/Tests.st +++ b/callagent/Tests.st @@ -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 [ + 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.