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

Merge commit 'd5248eceecd9d2f8c7061538163bc8ec80168dfc'

This commit is contained in:
Holger Hans Peter Freyther 2015-01-23 09:36:54 +01:00
commit 6708e54159
4 changed files with 32 additions and 8 deletions

View File

@ -39,6 +39,11 @@ Object subclass: MGCPEndpoint [
^ trunk endpointName: nr.
]
endpointNumber [
<category: 'accessing'>
^ nr
]
multiplex [
<category: 'names'>
^ trunk multiplexFor: nr.
@ -83,7 +88,7 @@ Object subclass: MGCPEndpoint [
<category: 'allocation'>
state = aState ifFalse: [
^ self error: 'MGCPEndpoint(%1) not %2.'
% {self endpointName. aState} area: #mgcp.
% {self endpointName. aState}.
].
]

View File

@ -23,9 +23,7 @@ Object subclass: MGCPTrunkBase [
MGCPTrunkBase class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
^self basicNew initialize
]
initialize [

View File

@ -115,8 +115,10 @@ TestCase subclass: MGCPCommandTest [
| trunk |
trunk := MGCPDSTrunk createWithDest: '0.0.0.0' trunkNr: 3.
self assert: (self trunk endpointAt: 1) endpointNumber equals: 1.
self assert: (self trunk endpointAt: 1) multiplex = 0.
self assert: (self trunk endpointAt: 1) timeslot = 1.
self assert: (self trunk endpointAt: 31) endpointNumber equals: 31.
self assert: (self trunk endpointAt: 31) multiplex = 0.
self assert: (self trunk endpointAt: 31) timeslot = 31.
@ -150,9 +152,7 @@ MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPMockNoTransmitAgent class >> new [
^ super new
initialize;
yourself
^self basicNew initialize
]
initialize [
@ -284,6 +284,7 @@ TestCase subclass: MGCPEndpointAllocTest [
"Initial..."
self assert: endp isUnused.
self assert: endp endpointNumber equals: 1.
"Reserve..."
endp reserve.
@ -334,6 +335,7 @@ TestCase subclass: MGCPEndpointAllocTest [
self assert: (trunk allocateEndpointIfFailure: [true]).
"now free some endpoints"
self assert: (trunk endpointAt: 20) endpointNumber equals: 20.
(trunk endpointAt: 20) free.
(trunk endpointAt: 5) free.
endp := (trunk allocateEndpointIfFailure: []).
@ -377,10 +379,28 @@ PP.PPCompositeParserTest subclass: MGCPParserTest [
]
exampleCRCXWithOsmux [
^String streamContents: [:stream |
stream
nextPutAll: 'CRCX 361562151 1@mgw MGCP 1.0'; nl;
nextPutAll: 'X-Osmux: on'; cr; nl;
nextPutAll: 'C: f553fcb979'; cr; nl;
nextPutAll: 'L: p:20, a:AMR, nt:IN'; cr; nl;
nextPutAll: 'M: recvonly'; cr; nl
]
]
parserClass [
^MGCPParser
]
testParseCRCXWithOsmux [
| crcx |
crcx := self parse: self exampleCRCXWithOsmux.
self assert: crcx class verb equals: 'CRCX'.
]
testParseCRCX [
| crcx |
crcx := self parse: self class crcxMessage.

View File

@ -130,7 +130,8 @@ PP.PPCompositeParser subclass: MGCPGrammar [
('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)
('X-Osmo-CP' asParser, $: asParser, #blank asParser star, self wordParser star flatten) /
('X-Osmux' asParser, $: asParser, #blank asParser star, self wordParser star flatten)
]
MGCPResponse [