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/Tests.st

234 lines
6.3 KiB
Smalltalk

"
(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/>.
"
TestCase subclass: MGCPCommandTest [
| trunk callagent |
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: 32]
]
endpoint [
^ self trunk endpointAt: 20.
]
exampleCRCX [
| crnl |
^ (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')
parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN';
parameterAdd: 'M: recvonly';
yourself.
trans command: crcx.
self assert: crcx asDatagram = self exampleCRCX.
]
tearDown [
self callagent stop.
]
]
MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
| send |
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 |
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 dropAgent |
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')
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.
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')
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.
]
]
TestCase subclass: MGCPEndpointAllocTest [
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.
]
]