smalltalk
/
osmo-st-mgcp
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-mgcp/callagent/MGCPCommands.st

233 lines
5.7 KiB
Smalltalk

"
(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 <http://www.gnu.org/licenses/>.
"
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'>
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 [
<category: 'verb'>
^ self subclassResponsibility
]
endpoint: anEndpoint [
<category: 'private'>
endp := anEndpoint.
]
transactionId: anId [
<category: 'private'>
transaction := anId.
]
transactionId [
^transaction
]
parameterAdd: aParam [
<category: 'private'>
^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 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 [
<category: 'private'>
^ params ifNil: [params := OrderedCollection new]
]
sdp: aRecord [
<category: 'private'>
sdp := aRecord.
]
sdp [
<category: 'private'>
^ sdp
]
asDatagram [
| out |
<category: 'networking'>
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 [
<comment: 'I represent a CRCX message'>
<category: 'OsmoMGCP-Callagent'>
MGCPCRCXCommand class >> verb [
<category: 'verb'>
^ 'CRCX'
]
MGCPCRCXCommand class >> createCRCX: anEndpoint callId: aCallId [
<category: 'factory'>
"I create a CRCX command for the given endpoint."
^ (self create: anEndpoint callId: aCallId)
yourself
]
]
MGCPCommandBase subclass: MGCPMDCXCommand [
<comment: 'I represent a MDCX message'>
<category: 'OsmoMGCP-Callagent'>
MGCPMDCXCommand class >> verb [
<category: 'verb'>
^ 'MDCX'
]
MGCPMDCXCommand class >> createMDCX: anEndpoint callId: aCallId [
<category: 'factory'>
^ (self create: anEndpoint callId: aCallId)
yourself
]
]
MGCPCommandBase subclass: MGCPDLCXCommand [
<comment: 'I represent a DLCX message'>
<category: 'OsmoMGCP-Callagent'>
MGCPDLCXCommand class >> verb [
<category: 'verb'>
^ 'DLCX'
]
MGCPDLCXCommand class >> createDLCX: anEndpoint callId: aCallId [
^ (self create: anEndpoint callId: aCallId)
yourself
]
]
MGCPCommandBase subclass: MGCPAUEPCommand [
<comment: 'I represent an AUEP message'>
<category: 'OsmoMGCP-Callagent'>
MGCPAUEPCommand class >> verb [
<category: 'verb'>
^ 'AUEP'
]
MGCPAUEPCommand class >> createAUEP: anEndpoint [
^ (self create: anEndpoint)
yourself
]
]
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'>
MGCPOsmoRSIPCommand class >> verb [
<category: 'verb'>
^ 'RSIP'
]
MGCPOsmoRSIPCommand class >> createRSIP [
^ self new
]
]