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

142 lines
3.5 KiB
Smalltalk
Raw Normal View History

"
(C) 2010-2011 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: MGCPCommand [
| verb 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: 'MGCP-callagent'>
verb: aVerb [
<category: 'private'>
verb := aVerb.
]
endpoint: anEndpoint [
<category: 'private'>
endp := anEndpoint.
]
transactionId: anId [
<category: 'private'>
transaction := anId.
]
parameterAdd: aParam [
<category: 'private'>
self params add: aParam.
]
params [
<category: 'private'>
^ params ifNil: [params := OrderedCollection new]
]
sdpAdd: line [
<category: 'private'>
self sdp add: line.
]
sdp [
<category: 'private'>
^ sdp ifNil: [sdp := OrderedCollection new]
]
asDatagram [
| out |
<category: 'networking'>
out := WriteStream on: (String new).
"write the header"
out
nextPutAll: '%1 %2 %3 MGCP 1.0' % {verb. transaction. endp};
cr; nl.
"write the parameters"
params do: [:each |
out
nextPutAll: each;
cr; nl.
].
"write optional SDP"
sdp ifNotNil: [
out
cr; nl.
sdp do: [:each |
out
nextPutAll: each;
cr; nl.
].
].
^ out contents
]
]
MGCPCommand subclass: MGCPCRCXCommand [
<comment: 'I represent a CRCX message'>
<category: 'MGCP-callagent'>
MGCPCRCXCommand class >> createCRCX: anEndpoint callId: aCallId transId: aTransId [
<category: 'factory'>
"I create a CRCX command for the given endpoint."
^ (self new)
verb: 'CRCX';
transactionId: aTransId;
endpoint: anEndpoint;
parameterAdd: 'M: recvonly';
parameterAdd: 'C: ', aCallId asString;
yourself
]
]
MGCPCommand subclass: MGCPMDCXCommand [
<comment: 'I represent a MDCX message'>
<category: 'MGCP-Callagent'>
MGCPMDCXCommand class >> createMDCX: anEndpoint callId: aCallId transId: aTransId [
<category: 'factory'>
^ (self new)
verb: 'MDCX';
transactionId: aTransId;
endpoint: anEndpoint;
parameterAdd: 'C: ', aCallId asString;
yourself
]
]
MGCPCommand subclass: MGCPDLCXCommand [
<comment: 'I represent a DLCX message'>
<category: 'MGCP-Callagent'>
MGCPDLCXCommand class >> createDLCX: anEndpoint callId: aCallId transId: aTransId [
^ (self new)
verb: 'DLCX';
transactionId: aTransId;
endpoint: anEndpoint;
parameterAdd: 'C: ', aCallId asString;
yourself
]
]