" (C) 2010-2012 by Holger Hans Peter Freyther All Rights Reserved This program is free software: you can redistribute it and/or modify it under the terms of the GNU Affero General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more details. You should have received a copy of the GNU Affero General Public License along with this program. If not, see . " Object subclass: MGCPCommandBase [ | transaction endp params sdp | MGCPCommandBase class >> fromDict: nodes [ | verb | verb := nodes first. self allSubclassesDo: [:each | each verb = verb ifTrue: [^each parseFromDict: nodes]]. ^self error: ('Unknown command verb "<1s>"' expandMacrosWith: verb). ] MGCPCommandBase class >> parseFromDict: nodes [ ^self new transactionId: nodes third; endpoint: (nodes at: 5); addParametersInternal: (nodes at: 9); sdp: (MGCPResponse sdpFromDict: (nodes at: 10)); yourself ] 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 ] MGCPCommandBase class >> verb [ ^ self subclassResponsibility ] endpoint: anEndpoint [ endp := anEndpoint. ] transactionId: anId [ transaction := anId. ] transactionId [ ^transaction ] parameterAdd: 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 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 [ ^ params ifNil: [params := OrderedCollection new] ] sdp: aRecord [ sdp := aRecord. ] sdp [ ^ sdp ] asDatagram [ | out | out := WriteStream on: (String new). "write the header" out nextPutAll: self class verb; nextPutAll: ' '; nextPutAll: transaction asString; nextPutAll: ' '; nextPutAll: endp; nextPutAll: ' MGCP 1.0'; cr; nl. "write the parameters" self params do: [:each | out nextPutAll: each key; nextPutAll: ': '; nextPutAll: each value; cr; nl. ]. "write optional SDP" sdp ifNotNil: [ out cr; nl; nextPutAll: sdp. ]. ^ out contents ] ] MGCPCommandBase subclass: MGCPCRCXCommand [ MGCPCRCXCommand class >> verb [ ^ 'CRCX' ] MGCPCRCXCommand class >> createCRCX: anEndpoint callId: aCallId [ "I create a CRCX command for the given endpoint." ^ (self create: anEndpoint callId: aCallId) yourself ] ] MGCPCommandBase subclass: MGCPMDCXCommand [ MGCPMDCXCommand class >> verb [ ^ 'MDCX' ] MGCPMDCXCommand class >> createMDCX: anEndpoint callId: aCallId [ ^ (self create: anEndpoint callId: aCallId) yourself ] ] MGCPCommandBase subclass: MGCPDLCXCommand [ MGCPDLCXCommand class >> verb [ ^ 'DLCX' ] MGCPDLCXCommand class >> createDLCX: anEndpoint callId: aCallId [ ^ (self create: anEndpoint callId: aCallId) yourself ] ] MGCPCommandBase subclass: MGCPAUEPCommand [ MGCPAUEPCommand class >> verb [ ^ 'AUEP' ] MGCPAUEPCommand class >> createAUEP: anEndpoint [ ^ (self create: anEndpoint) yourself ] ] MGCPCommandBase subclass: MGCPOsmoRSIPCommand [ MGCPOsmoRSIPCommand class >> verb [ ^ 'RSIP' ] MGCPOsmoRSIPCommand class >> createRSIP [ ^ self new ] ]