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

Add 'osmo-st-mgcp/' from commit '948264560fa608c487bf3cccd2055cb919ebbbb0'

git-subtree-dir: osmo-st-mgcp
git-subtree-mainline: 3ee982fe7a
git-subtree-split: 948264560f
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:02 +02:00
commit ef0d35037f
16 changed files with 13670 additions and 0 deletions

1
osmo-st-mgcp/.gitignore vendored Normal file
View File

@ -0,0 +1 @@
*.sw?

25
osmo-st-mgcp/DESIGN Normal file
View File

@ -0,0 +1,25 @@
Some simple design notes to guide people
- MGCPGrammar can parse requests and replies
- MGCPCommand base class of commands
- asDatagram to create message
- MGCPTrunk a trunk with a destination and nr. endpoints
- MGCPVirtualTrunk for 1@mgw.. in hex
- MGCPE1Trunk for ds-1/... handling
- both hold MGCPEndpoints
- MGCPTransaction a command to create a transaction
- callback for completion (wth response)
- callback for a timeout
- created with an endpoint and the callagent
- MGCPCallAgent serves the Call-Agent port
- Generates the transaction id for a transaction
- Does the retransmission
- Handles timeout
- Recycles transaction after three minutes
(to block a transaction identifier)

5
osmo-st-mgcp/README Normal file
View File

@ -0,0 +1,5 @@
This is a MGCP CallAgent written in Smalltalk.
The request to manage an allocation is coming from Smalltalk and
it will hanlde the code to send the requests to the MGWs involved.

View File

@ -0,0 +1,164 @@
"
(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/>.
"
PackageLoader
fileInPackage: 'Sockets';
fileInPackage: 'OsmoNetwork'.
Object subclass: MGCPCallAgentBase [
| net trunks sem addr port |
<category: 'OsmoMGCP-Callagent'>
<comment: 'I am responsible for the networking'>
MGCPCallAgentBase class >> startOn: anAddress [
<category: 'creation'>
^ (self new)
initialize: anAddress port: 2727;
yourself.
]
MGCPCallAgentBase class >> startOn: anAddress port: aPort [
<category: 'creation'>
^ self new
initialize: anAddress port: aPort;
yourself.
]
initialize: anAddress port: aPort [
<category: 'creation'>
sem := Semaphore forMutualExclusion.
trunks := OrderedCollection new.
addr := anAddress.
port := aPort.
net := Osmo.OsmoUDPSocket new
name: 'MGCPCallAgent';
onData: [:data | OsmoDispatcher dispatchBlock: [self handleData: data]];
yourself.
]
addTrunk: aTrunk [
<category: 'setup'>
sem critical: [
trunks add: aTrunk.
].
]
handleData: aData [
<category: 'handling'>
^ self subclassResponsibility
]
start [
| socket |
<category: 'handling'>
self stop.
socket := (Sockets.DatagramSocket local: addr port: port)
bufferSize: 2048;
yourself.
net start: socket.
]
stop [
<category: 'processing'>
net stop
]
queueData: aDatagram [
<category: 'sending'>
net queueData: aDatagram.
]
]
MGCPCallAgentBase subclass: MGCPCallAgent [
| transactions parser |
<category: 'OsmoMGCP-Callagent'>
<comment: 'I deal with transactions and timeouts'>
initialize: anAddress port: aPort [
<category: 'private'>
super initialize: anAddress port: aPort.
transactions := OrderedCollection new.
]
addTransaction: aTransaction [
<category: 'private'>
sem critical: [
aTransaction transactionId: self generateTransactionId.
transactions add: aTransaction.
]
]
removeTransactionInternal: aTransaction [
<category: 'private'>
sem critical: [transactions remove: aTransaction].
]
transactionIdIsUsed: anId [
<category: 'private'>
^ transactions anySatisfy: [:each | each transactionId = anId]
]
generateTransactionId [
| ran |
<category: 'private'>
"I need to generate a transaction identifier. I assume proper locking"
"Check if the below could ever succeed"
(transactions size - 500000) > (999999999 - 100000000) ifTrue: [
^ self error: 'No free transaction ID.'.
].
[
ran := Random between: 100000000 and: 999999999.
self transactionIdIsUsed: ran
] whileTrue.
^ ran.
]
parser [
<category: 'private'>
^ parser ifNil: [parser := MGCPParser new]
]
handleData: aData [
[
| res data id trans |
data := aData data copyFrom: 1 to: aData size.
res := self parser parse: data asString onError: [
^ self error: 'Parse error ', data asByteArray printString.
].
id := res transactionId asInteger.
trans := sem critical: [transactions copy].
trans do: [:each |
each transactionId = id ifTrue: [
each response: res.
]
]
] on: Error do: [:e |
e logException: 'Incoming data ', e tag area: #mgcp.
]
]
]

View File

@ -0,0 +1,227 @@
"
(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 "%1"' % {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 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 [
<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: '%1 %2 %3 MGCP 1.0' % {self class verb. transaction. endp};
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
]
]

View File

@ -0,0 +1,164 @@
"
(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: MGCPEndpoint [
| nr trunk state callid connid sdp|
<category: 'OsmoMGCP-Callagent'>
<comment: 'I am one endpoint. I have a state...'>
MGCPEndpoint class >> stateUnused [ <category: 'states'> ^ #unused ]
MGCPEndpoint class >> stateReserved [ <category: 'states'> ^ #reserved ]
MGCPEndpoint class >> stateUsed [ <category: 'states'> ^ #used ]
MGCPEndpoint class >> stateBlocked [ <category: 'states'> ^ #blocked ]
MGCPEndpoint class >> initWith: aNr trunk: aTrunk [
^ self new
instVarNamed: #nr put: aNr;
instVarNamed: #trunk put: aTrunk;
instVarNamed: #state put: self stateUnused;
yourself
]
endpointName [
<category: 'names'>
^ trunk endpointName: nr.
]
multiplex [
<category: 'names'>
^ trunk multiplexFor: nr.
]
timeslot [
<category: 'names'>
^ trunk timeslotFor: nr.
]
trunk [
<category: 'private'>
^ trunk
]
state [
<category: 'state'>
^ state
]
isBlocked [
<category: 'state'>
^ state = self class stateBlocked.
]
isReserved [
<category: 'state'>
^ state = self class stateReserved.
]
isUnused [
<category: 'state'>
^ state = self class stateUnused.
]
isUsed [
<category: 'state'>
^ state = self class stateUsed.
]
requireState: aState [
<category: 'allocation'>
state = aState ifFalse: [
^ self error: 'MGCPEndpoint(%1) not %2.'
% {self endpointName. aState} area: #mgcp.
].
]
reserve [
<category: 'allocation'>
self requireState: self class stateUnused.
state := self class stateReserved.
]
used [
<category: 'allocation'>
self requireState: self class stateReserved.
state := self class stateUsed.
]
free [
<category: 'allocation'>
self requireState: self class stateUsed.
state := self class stateUnused.
sdp := nil.
callid := nil.
connid := nil.
]
tryBlock [
<category: 'allocation'>
state = self class stateUnused ifTrue: [
state := self class stateBlocked.
^ true
].
^ false
]
unblock [
<category: 'allocation'>
self requireState: self class stateBlocked.
state := self class stateUnused.
]
sdp [
<category: 'sdp'>
^ sdp
]
sdp: aSdp [
<category: 'sdp'>
self requireState: self class stateUsed.
sdp := aSdp.
]
callId [
<category: 'callid'>
^ callid
]
callId: aCallId [
<category: 'callid'>
self requireState: self class stateReserved.
callid := aCallId.
]
clearCallId [
<category: 'callid'>
self requireState: self class stateUsed.
callid := nil.
]
connId [
<category: 'connid'>
^ connid
]
connId: aConnId [
self requireState: self class stateUsed.
connid := aConnId.
]
]

View File

@ -0,0 +1,35 @@
"
(C) 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/>.
"
PackageLoader fileInPackage: #OsmoLogging.
Osmo.LogArea subclass: MGCPLogArea [
<category: 'OsmoMGCP-Logging'>
MGCPLogArea class >> areaName [ ^ #mgcp ]
MGCPLogArea class >> areaDescription [
^ 'MGCP LogArea'
]
MGCPLogArea class >> default [
^ self new
enabled: true;
minLevel: LogLevel notice;
yourself
]
]

View File

@ -0,0 +1,41 @@
"
(C) 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/>.
"
MGCPGrammar subclass: MGCPParser [
<category: 'OsmoMGCP-Parser'>
<comment: 'I parse responses for now.'>
MGCPMessage [
<category: 'extract'>
^ super MGCPMessage => [:nodes | nodes]
]
MGCPCommand [
<category: 'extract'>
^ super MGCPCommand => [:nodes | MGCPCommandBase fromDict: nodes]
]
MGCPResponse [
<category: 'extract'>
^ super MGCPResponse => [:nodes | MGCPResponse fromDict: nodes]
]
endpointName [
^super endpointName flatten
]
]

View File

@ -0,0 +1,107 @@
"
(C) 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: MGCPResponse [
| code transaction params sdp |
<category: 'OsmoMGCP-Response'>
<comment: 'I provide a nicer way to look at responses'>
MGCPResponse class >> fromDict: aDict [
<category: 'creation'>
^ self new
initialize;
responseCode: aDict first first;
transaction: aDict first third;
addParamsFromDict: aDict second;
addSDPFromDict: aDict third;
yourself
]
MGCPResponse class >> sdpFromDict: aDict [
| str |
aDict isNil ifTrue: [
^nil
].
str := WriteStream on: (String new).
^String streamContents: [:stream |
aDict second do: [:each |
stream
nextPutAll: each first;
cr; nl.]]
]
initialize [
<category: 'creation'>
params := Dictionary new.
]
responseCode: aCode [
<category: 'creation'>
code := aCode asInteger
]
transaction: aTrans [
<category: 'creation'>
self transactionId: aTrans
]
transactionId: aTrans [
<category: 'creation'>
transaction := aTrans.
]
addParamsFromDict: aList [
<category: 'creation'>
aList do: [:each |
params at: each first first asString put: each first fourth].
]
addSDPFromDict: aDict [
<category: 'creation'>
sdp := self class sdpFromDict: aDict.
]
transactionId [
<category: 'accessing'>
^ transaction
]
code [
<category: 'accessing'>
^ code
]
isSuccess [
<category: 'accessing'>
^ code >= 200 and: [code < 300].
]
sdp [
<category: 'accessing'>
^ sdp
]
parameterAt: aKey ifAbsent: aBlock [
^ params at: aKey ifAbsent: aBlock.
]
]

View File

@ -0,0 +1,228 @@
"
(C) 2011-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/>.
"
PackageLoader
fileInPackage: 'Sockets';
fileInPackage: 'OsmoCore'.
Object subclass: MGCPTransactionBase [
| callagent t_retransmit t_expire t_remove sem |
<comment: 'I handle timers for the transaction'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransactionBase class >> on: aCallagent [
^ self new
initialize;
callagent: aCallagent;
yourself
]
MGCPTransactionBase class >> retransmitTime [ <category: 'timeouts'> ^ 10 ]
MGCPTransactionBase class >> expireTime [ <category: 'timeouts'> ^ 60 ]
MGCPTransactionBase class >> removeTime [ <category: 'timeouts'> ^ 3 * 60 ]
initialize [
<category: 'creation'>
sem := RecursionLock new.
]
callagent: aCallagent [
<category: 'private'>
callagent := aCallagent.
callagent addTransaction: self.
]
callagent [
<category: 'private'>
^ callagent
]
schedule: aTime block: aBlock [
<category: 'helper'>
^ Osmo.TimerScheduler instance scheduleInSeconds: aTime
block: aBlock.
]
startRetransmitTimer [
<category: 'private'>
sem critical: [
t_retransmit ifNotNil: [t_retransmit cancel].
t_retransmit := self schedule: self class retransmitTime
block: [self transactionRetransmit].
]
]
stopRetransmitTimer [
<category: 'private'>
sem critical: [
t_retransmit ifNotNil: [t_retransmit cancel].
]
]
started [
<category: 'public'>
t_expire := self schedule: self class expireTime
block: [self transactionExpired].
t_remove := self schedule: self class removeTime
block: [self transactionRemoved].
]
completed [
<category: 'public'>
sem critical: [
t_retransmit cancel.
t_expire cancel.
]
]
]
MGCPTransactionBase subclass: MGCPTransaction [
| result timeout id command endpoint state |
<comment: 'I am a transaction...'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransaction class >> on: endpoint of: callagent [
| res |
<category: 'factory'>
^ (self on: callagent)
instVarNamed: #endpoint put: endpoint;
yourself.
]
MGCPTransaction class >> stateInitial [ ^ 0 ]
MGCPTransaction class >> stateStarted [ ^ 1 ]
MGCPTransaction class >> stateFinished [ ^ 2 ]
transactionId [
<category: 'accessing'>
^ id
]
state [
<category: 'state'>
^ state ifNil: [state := self class stateInitial]
]
transactionId: anId [
<category: 'private'>
id := anId.
]
command [
<category: 'creation'>
^ command
]
command: aMGCPCommand [
<category: 'configuration'>
command := aMGCPCommand.
command transactionId: id.
command endpoint: endpoint endpointName.
]
onResult: aBlock [
<category: 'callback'>
result := aBlock
]
onTimeout: aBlock [
<category: 'callback'>
timeout := aBlock
]
start [
<category: 'network'>
state := self class stateStarted.
self started.
^ self sendData
]
startSingleShot [
<category: 'network'>
state := self class stateStarted.
self started.
^ self sendDataDirect
]
sendData [
<category: 'private'>
self startRetransmitTimer.
self sendDataDirect
]
sendDataDirect [
<category: 'private'>
| datagram |
datagram := Sockets.Datagram data: (command asDatagram)
address: (Sockets.SocketAddress
byName: endpoint trunk destIp)
port: 2427.
self callagent queueData: datagram.
]
response: aRes [
"Handle response but only once"
state = self class stateStarted ifFalse: [
^ self logError: 'Transaction(ID:%1 verb:%2) already terminated'
% {id. command class verb} area: #mgcp.
].
"Remember things for the future"
self logNotice: 'Transaction(ID:%1 verb:%2) got a response.'
% {id. command class verb} area: #mgcp.
state := self class stateFinished.
self completed.
"completed..."
result ifNotNil: [
result value: self value: aRes.
].
]
transactionRemoved [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) is finished. %3'
% {id. command class verb. DateTime now} area: #mgcp.
self callagent removeTransactionInternal: self.
]
transactionExpired [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) expired. %3'
% {id. command class verb. DateTime now} area: #mgcp.
state := self class stateFinished.
self stopRetransmitTimer.
timeout ifNotNil: [
timeout value: self.
]
]
transactionRetransmit [
<category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) retransmit.'
% {id. command class verb} area: #mgcp.
self sendData.
]
]

View File

@ -0,0 +1,162 @@
"
(C) 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: MGCPTrunkBase [
| ip ports sem last |
<comment: 'I represent a trunk for a Gateway'>
<category: 'OsmoMGCP-Callagent'>
MGCPTrunkBase class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
]
initialize [
sem := RecursionLock new.
]
destIp [
<category: 'accessing'>
^ ip
]
destIP: aDest [
<category: 'private'>
ip := aDest
]
numbersPorts: nrPorts [
<category: 'private'>
ports := Array new: nrPorts.
1 to: nrPorts do: [:each |
ports at: each put: (MGCPEndpoint initWith: each trunk: self)].
]
endpointAt: aNr [
<category: 'private'>
^ ports at: aNr
]
lastUsed [
<category: 'private'>
^ last ifNil: [0]
]
endpointName: aNr [
<category: 'accessing'>
^ self subclassResponsibility
]
multiplexFor: aNr [
<category: 'accessing'>
^ self subclassResponsibility.
]
timeslotFor: aNr [
<category: 'accessing'>
^ self subclassResponsibility.
]
critical: aBlock [
<category: 'accessing'>
sem critical: aBlock.
]
allocateEndpointIfFailure: aBlock [
| alloc |
<category: 'allocation'>
"You need to hold the lock to do any changes here"
alloc := [:each |
(self endpointAt: each) isUnused ifTrue: [
last := each.
^ (self endpointAt: each)
reserve;
yourself
]].
"Go from last to end, and then from start to last."
self lastUsed + 1 to: ports size do: alloc.
1 to: self lastUsed do: alloc.
"And give up now"
^ aBlock value.
]
]
MGCPTrunkBase subclass: MGCPVirtualTrunk [
<comment: 'I represent a @mgw virtual trunk'>
<category: 'OsmoMGCP-Callagent'>
MGCPVirtualTrunk class >> createWithDest: anIP numberPorts: nr [
<category: 'factory'>
^ self new
destIP: anIP;
numbersPorts: nr
yourself
]
endpointName: aNr [
<category: 'accessing'>
^ '%1@mgw' % {((aNr radix: 16) copyFrom: 4) asLowercase}
]
multiplexFor: aNr [
<category: 'accessing'>
^ aNr // 32
]
timeslotFor: aNr [
<category: 'accessing'>
^ aNr \\ 32
]
]
MGCPTrunkBase subclass: MGCPDSTrunk [
| trunk |
<comment: 'I represent an E1 trunk with 32 endpoints'>
<category: 'OsmoMGCP-Callagent'>
MGCPDSTrunk class >> createWithDest: anIP trunkNr: aNr [
<category: 'factory'>
^ self new
destIP: anIP;
numbersPorts: 31;
trunkNr: aNr;
yourself
]
trunkNr: aNr [
trunk := aNr.
]
endpointName: aNr [
<category: 'accessing'>
^ 'ds/e1-%1/%2@mgw' % {trunk. aNr}
]
multiplexFor: aNr [
^ trunk
]
timeslotFor: aNr [
^ aNr \\ 32
]
]

View File

@ -0,0 +1,432 @@
"
(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/>.
"
TestCase subclass: MGCPCommandTest [
| trunk callagent |
<category: 'OsmoMGCP-Callagent-Tests'>
callagent [
^ callagent ifNil: [
callagent := MGCPCallAgent startOn: '127.0.0.1' port: 0.
callagent addTrunk: self trunk; yourself].
]
trunk [
^ trunk ifNil: [
trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 31]
]
endpoint [
^ self trunk endpointAt: 20.
]
exampleSDP [
<category: 'private'>
^ (WriteStream on: String new)
nextPutAll: 'v=0'; cr; nl;
nextPutAll: 'o=- 258696477 0 IN IP4 172.16.1.107'; cr; nl;
nextPutAll: 'c=IN IP4 172.16.1.107'; cr; nl;
nextPutAll: 't=0 0'; cr; nl;
nextPutAll: 'm=audio 6666 RTP/AVP 127'; cr; nl;
nextPutAll: 'a=rtpmap:127 GSM-EFR/8000/1'; cr; nl;
nextPutAll: 'a=ptime:20'; cr; nl;
nextPutAll: 'a=recvonly'; cr; nl;
nextPutAll: 'm=image 4402 udptl t38'; cr; nl;
nextPutAll: 'a=T38FaxVersion:0'; cr; nl;
nextPutAll: 'a=T38MaxBitRate:14400'; cr; nl;
contents
]
exampleMDCX [
^ (WriteStream on: String new)
nextPutAll: 'MDCX 808080 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;
cr; nl;
nextPutAll: self exampleSDP;
contents
]
exampleCRCX [
^ (WriteStream on: String new)
nextPutAll: 'CRCX 808080 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;
contents
]
testCRCXCreation [
| crcx trans |
trans := MGCPTransaction on: self endpoint of: self callagent.
trans transactionId: '808080'.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
self assert: crcx asDatagram = self exampleCRCX.
]
exampleRSIP [
^ (WriteStream on: String new)
nextPutAll: 'RSIP 808080 14@mgw MGCP 1.0'; cr; nl;
contents
]
testRSIPCreation [
| trans |
trans := (MGCPTransaction on: self endpoint of: self callagent)
transactionId: '808080';
command: (MGCPOsmoRSIPCommand createRSIP);
yourself.
self assert: trans command asDatagram = self exampleRSIP.
]
testEndPointName [
| trunk |
trunk := MGCPDSTrunk createWithDest: '0.0.0.0' trunkNr: 1.
"I test the endpoint name on hex part.."
self assert: (MGCPVirtualTrunk new endpointName: 16rA) = 'a@mgw'.
self assert: (trunk endpointName: 16rA) = 'ds/e1-1/10@mgw'.
]
testMultiplexTimeslot [
| trunk |
trunk := MGCPDSTrunk createWithDest: '0.0.0.0' trunkNr: 3.
self assert: (self trunk endpointAt: 1) multiplex = 0.
self assert: (self trunk endpointAt: 1) timeslot = 1.
self assert: (self trunk endpointAt: 31) multiplex = 0.
self assert: (self trunk endpointAt: 31) timeslot = 31.
self assert: (trunk endpointAt: 1) multiplex = 3.
self assert: (trunk endpointAt: 31) timeslot = 31.
]
testMDCXWithSDP [
| mdcx trans |
trans := MGCPTransaction on: self endpoint of: self callagent.
trans transactionId: '808080'.
mdcx := (MGCPMDCXCommand createMDCX: self endpoint callId: '4a84ad5d25f')
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
sdp: self exampleSDP;
yourself.
trans command: mdcx.
mdcx asDatagram printNl.
self assert: mdcx asDatagram = self exampleMDCX.
]
tearDown [
self callagent stop.
]
]
MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
| send |
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPMockNoTransmitAgent class >> new [
^ super new
initialize;
yourself
]
initialize [
send := Semaphore new.
]
queueData: aDatagram [
send signal
]
sends [
[^send signals]
ensure: [send := Semaphore new]
]
]
MGCPMockNoTransmitAgent subclass: MGCPTransmitSecond [
| drop |
<category: 'OsmoMGCP-Callagent-Tests'>
initialize [
drop := true.
^ super initialize.
]
queueData: aData [
super queueData: aData.
drop
ifTrue: [drop := false]
ifFalse: [drop := true. transactions first response: 3.].
]
]
MGCPTransaction subclass: MGCPShortTransaction [
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPShortTransaction class >> retransmitTime [ ^ 1 ]
MGCPShortTransaction class >> expireTime [ ^ 6 ]
]
TestCase subclass: MGCPTransactionTest [
| trunk callagent dropAgent |
<category: 'OsmoMGCP-Callagent-Tests'>
timeoutCallagent [
^ callagent ifNil: [
callagent := MGCPMockNoTransmitAgent startOn: '127.0.0.1' port: 0.
callagent addTrunk: self trunk; yourself].
]
dropAgent [
^ dropAgent ifNil: [
dropAgent := MGCPTransmitSecond startOn: '127.0.0.1' port: 0.
dropAgent addTrunk: self trunk; yourself].
]
trunk [
^ trunk ifNil: [
trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32]
]
endpoint [
^ self trunk endpointAt: 20.
]
testTimeout [
| crcx trans result timeout |
trans := MGCPShortTransaction on: self endpoint of: self timeoutCallagent.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
result := Semaphore new.
timeout := Semaphore new.
trans
onResult: [:a :b | result signal];
onTimeout: [:each | timeout signal];
start.
timeout wait.
self assert: result signals = 0.
self assert: timeout signals = 0.
self assert: self timeoutCallagent sends > 6.
]
testSuccess [
| crcx trans result timeout |
trans := MGCPShortTransaction on: self endpoint of: self dropAgent.
crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f')
addParameter: 'L' with: 'p:20, a:GSM-EFR, nt:IN';
addParameter: 'M' with: 'recvonly';
yourself.
trans command: crcx.
result := Semaphore new.
timeout := Semaphore new.
trans
onResult: [:a :b | result signal];
onTimeout: [:each | timeout signal];
start.
result wait.
self assert: result signals = 0.
self assert: timeout signals = 0.
self assert: self dropAgent sends >= 2.
]
tearDown [
self timeoutCallagent stop.
self dropAgent stop.
]
]
TestCase subclass: MGCPEndpointAllocTest [
<category: 'OsmoMGCP-Callagent-Tests'>
testStateTransition [
| trunk endp |
trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32.
endp := trunk endpointAt: 1.
"Initial..."
self assert: endp isUnused.
"Reserve..."
endp reserve.
self assert: endp isReserved.
self should: [endp reserve] raise: Error.
self should: [endp free] raise: Error.
self should: [endp unblock] raise: Error.
self deny: endp tryBlock.
"Move to used..."
endp used.
self assert: endp isUsed.
self should: [endp reserve] raise: Error.
self should: [endp used] raise: Error.
self should: [endp unblock] raise: Error.
self deny: endp tryBlock.
"Move to free..."
endp free.
self assert: endp isUnused.
self should: [endp used] raise: Error.
self should: [endp unblock] raise: Error.
self assert: endp tryBlock.
"Now try to block it..."
self assert: endp isBlocked.
self should: [endp reserve] raise: Error.
self should: [endp free] raise: Error.
self should: [endp used] raise: Error.
self deny: endp tryBlock.
"Now unblock and restore"
endp unblock.
self assert: endp isUnused.
]
testAllocation [
| trunk endp |
trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32.
1 to: 32 do: [:each |
self assert: ((trunk allocateEndpointIfFailure: [])
used; isUsed).
].
"test an allocation failure"
self assert: (trunk allocateEndpointIfFailure: [true]).
"now free some endpoints"
(trunk endpointAt: 20) free.
(trunk endpointAt: 5) free.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '5@mgw'.
"last_used should be five now"
(trunk endpointAt: 4) free.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '14@mgw'.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '4@mgw'.
]
]
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;
cr; nl;
nextPutAll: 'v=0'; cr; nl;
nextPutAll: 'b=0'; cr; nl]
]
MGCPParserTest class >> natDLCXMessage [
^String streamContents: [:stream |
stream
nextPutAll: 'DLCX nat-0 1@mgw MGCP 1.0'; 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.
]
testParseDLCX [
| dlcx |
dlcx := self parse: self class natDLCXMessage.
self assert: dlcx class verb equals: 'DLCX'.
self assert: dlcx asDatagram equals: self class natDLCXMessage.
]
testRespParse [
| nl res sdp |
nl := Character cr asString, Character nl asString.
sdp := 'v=0', nl,
'o=- 258696477 0 IN IP4 172.16.1.107', nl,
's=-', nl,
'c=IN IP4 172.16.1.107', nl,
't=0 0', nl,
'm=audio 6666 RTP/AVP 127', nl,
'a=rtpmap:127 GSM-EFR/8000/1', nl,
'a=ptime:20', nl,
'a=recvonly', nl,
'm=image 4402 udptl t38', nl,
'a=T38FaxVersion:0', nl,
'a=T38MaxBitRate:14400', nl.
res := self parse: '200 32323 OK', nl,
'I: 233434', nl,
nl,
sdp.
self assert: res code = 200.
self assert: res isSuccess.
self assert: res transactionId = '32323'.
self assert: res sdp = sdp.
self assert: (res parameterAt: 'I' ifAbsent: []) = '233434'.
]
testFailureResp [
| nl res |
nl := Character cr asString, Character nl asString.
res := self parse: '400 32323 OK', nl.
self deny: res isSuccess.
self assert: res sdp isNil.
]
]

11763
osmo-st-mgcp/docs/RFC3435.txt Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,187 @@
"
(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/>.
"
PackageLoader fileInPackage: 'PetitParser'.
PP.PPCompositeParser subclass: MGCPGrammar [
| MGCPMessage EOL One_WSP MGCPMessage MGCPCommandLine MGCPVerb transaction_id endpointName MGCPversion MGCPParameter MGCPCommand ParameterValue SDPRecord SDPLine SDPinformation MGCPResponseLine responseCode responseString packageName |
<category: 'OsmoMGCP-Core'>
<comment: 'I am a the Grammar of the Media Gateway Control Protocol'>
start [
<category: 'accessing'>
^ MGCPMessage end
]
EOL [
<category: 'grammar-common'>
^ (Character cr asParser, Character lf asParser) /
Character lf asParser
]
One_WSP [
<category: 'grammar-common'>
^ #blank asParser plus
]
MGCPMessage [
<category: 'grammar-common'>
^ MGCPCommand / self MGCPResponse
]
MGCPCommandLine [
<category: 'grammar-cmd'>
^ self MGCPVerb,
self One_WSP,
self transaction_id,
self One_WSP,
self endpointName,
self One_WSP,
self MGCPversion,
self EOL
]
MGCPVerb [
<category: 'grammar-cmd'>
^ 'EPCF' asParser /
'CRCX' asParser /
'MDCX' asParser /
'DLCX' asParser /
'RQNT' asParser /
'NTFY' asParser /
'AUEP' asParser /
'AUCX' asParser /
'RSIP' asParser
]
transaction_id [
<category: 'grammar-cmd'>
"Add Osmocom extension that starts with 'nat-'"
^ ((#digit asParser) min: 1 max: 9) flatten /
('nat-' asParser, (#digit asParser) min: 1 max: 9) flatten
]
endpointName [
<category: 'grammar-cmd'>
"simplified version"
^ #word asParser star flatten, $@ asParser, #word asParser star flatten
]
MGCPversion [
<category: 'grammar-cmd'>
"skipping the optional profilename for now"
^ 'MGCP' asParser, One_WSP, #digit asParser, $. asParser, #digit asParser
]
MGCPCommand [
<category: 'grammar-cmd'>
^ MGCPCommandLine, MGCPParameter star, SDPRecord optional
]
MGCPParameter [
<category: 'grammar-cmd'>
^ ParameterValue, EOL
]
wordParser [
^ #word asParser / #punctuation asParser / ' ' asParser
]
ParameterValue [
^ ($K asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($B asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($C asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($I asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($N asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($X asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($L asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($M asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($R asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($S asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($D asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($O asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($P asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($E asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($Z asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($Z asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('Z2' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('I2' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($F asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($Q asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($T asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('RM' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('RD' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
($A asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('ES' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('PL' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('MD' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('X-Osmo-CP' asParser, $: asParser, #blank asParser star, self wordParser star flatten)
]
MGCPResponse [
"
MGCPResponse = MGCPResponseLine 0*(MGCPParameter) *2(EOL *SDPinformation)
The *2 appears to be weird
"
^ MGCPResponseLine,
MGCPParameter star,
SDPRecord optional
]
responseCode [
<category: 'response'>
^ (#digit asParser, #digit asParser, #digit asParser) flatten
]
packageName [
"Not Complete yet"
"packageName = 1*(ALPHA / DIGIT / HYPHEN) ; Hyphen neither first or last"
<category: 'response'>
^ #letter asParser plus
]
responseString [
<category: 'response'>
^ #letter asParser plus flatten
]
MGCPResponseLine [
^ responseCode,
self One_WSP,
transaction_id,
(self One_WSP, '/' asParser, packageName) optional,
(self One_WSP, responseString) optional,
EOL
]
SDPRecord [
^ EOL, SDPinformation
]
SDPinformation [
^ (SDPLine, EOL) plus
]
SDPLine [
^ self wordParser star flatten
]
]
Eval [
MGCPGrammar initialize.
]

View File

@ -0,0 +1,102 @@
"
(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/>.
"
PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: MGCPGrammarTest [
<comment: 'I test some parts of the grammar'>
<category: 'OsmoMGCP-Core-Tests'>
MGCPGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>
^#('MGCPGrammar')
]
parserClass [
<category: 'accessing'>
^MGCPGrammar
]
testCommand [
<category: 'test-command'>
| res nl |
nl := Character cr asString, Character nl asString.
res := self parse: 'AUEP 23444 13@mgw MGCP 1.0',
nl,
'K: 3445', nl,
'I: 233434', nl,
'L: p:20, a:GSM-EFR, nt:IN', nl,
'M: recvonly', nl,
nl,
'v=0', nl,
'o=- 258696477 0 IN IP4 172.16.1.107', nl,
's=-', nl,
'c=IN IP4 172.16.1.107', nl,
't=0 0', nl,
'm=audio 6666 RTP/AVP 127', nl,
'a=rtpmap:127 GSM-EFR/8000/1', nl,
'a=ptime:20', nl,
'a=recvonly', nl,
'm=image 4402 udptl t38', nl,
'a=T38FaxVersion:0', nl,
'a=T38MaxBitRate:14400', nl.
self assert: res size = 10.
self assert: (res at: 1) = 'AUEP'.
self assert: (res at: 3) = '23444'.
self assert: (res at: 5) = #('13' $@ 'mgw').
res inspect.
]
testReply [
| res nl |
nl := Character cr asString, Character nl asString.
res := self parse: '200 123456 OK',
nl.
self assert: res size = 3.
self assert: res first first = '200'.
self assert: res first third = '123456'.
]
testReplyByte [
| res inp |
inp := #(50 48 48 32 52 51 51 52 49 52 54 53 54 32 79 75 13 10) asByteArray.
res := self parse: inp asString.
res inspect.
self assert: res size = 3.
self assert: res first first = '200'.
self assert: res first third = '433414656'.
]
testDlcxResponse [
| res inp |
inp := #[50 53 48 32 54 56 51 52 53 53 50 52 52 32 79 75 13 10 80 58 32 80 83 61 49 54 57 44 32 79 83 61 55 54 48 53 44 32 80 82 61 48 44 32 79 82 61 48 44 32 80 76 61 48 44 32 74 73 61 48 13 10 88 45 79 115 109 111 45 67 80 58 32 69 67 32 84 73 83 61 48 44 32 84 79 83 61 48 44 32 84 73 82 61 48 44 32 84 79 82 61 48 13 10].
res := self parse: inp asString.
res inspect.
]
]

27
osmo-st-mgcp/package.xml Normal file
View File

@ -0,0 +1,27 @@
<package>
<name>OsmoMGCP</name>
<namespace>Osmo</namespace>
<prereq>OsmoLogging</prereq>
<prereq>OsmoCore</prereq>
<filein>grammar/MGCPGrammar.st</filein>
<filein>callagent/MGCPCallAgent.st</filein>
<filein>callagent/MGCPCommands.st</filein>
<filein>callagent/MGCPResponse.st</filein>
<filein>callagent/MGCPEndpoint.st</filein>
<filein>callagent/MGCPLogArea.st</filein>
<filein>callagent/MGCPTransaction.st</filein>
<filein>callagent/MGCPTrunk.st</filein>
<filein>callagent/MGCPParser.st</filein>
<test>
<sunit>Osmo.MGCPGrammarTest</sunit>
<sunit>Osmo.MGCPCommandTest</sunit>
<sunit>Osmo.MGCPEndpointAllocTest</sunit>
<sunit>Osmo.MGCPTransactionTest</sunit>
<sunit>Osmo.MGCPParserTest</sunit>
<filein>grammar/MGCPGrammarTest.st</filein>
<filein>callagent/Tests.st</filein>
</test>
</package>