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

callagent: Test the success path of MGCPTransaction

This commit is contained in:
Holger Hans Peter Freyther 2011-06-23 17:47:40 +02:00
parent eb7736c08d
commit 82da2de559
1 changed files with 49 additions and 1 deletions

View File

@ -86,13 +86,30 @@ MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
]
]
MGCPMockNoTransmitAgent subclass: MGCPTransmitSecond [
| drop |
initialize [
drop := true.
^ super initialize.
]
queueData: aData [
super queueData: aData.
drop
ifTrue: [drop := false]
ifFalse: [drop := true. transactions first response: 3.].
]
]
MGCPTransaction subclass: MGCPShortTransaction [
MGCPShortTransaction class >> retransmitTime [ ^ 1 ]
MGCPShortTransaction class >> expireTime [ ^ 6 ]
]
TestCase subclass: MGCPTransactionTest [
| trunk callagent |
| trunk callagent dropAgent |
timeoutCallagent [
^ callagent ifNil: [
@ -100,6 +117,12 @@ TestCase subclass: MGCPTransactionTest [
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]
@ -133,7 +156,32 @@ TestCase subclass: MGCPTransactionTest [
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')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: 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.
]
]