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

modernize the test cases. Use >>#assert:equals:

This commit is contained in:
Holger Hans Peter Freyther 2015-07-24 18:28:12 +02:00
parent 31c7c8e55b
commit ed9b198256
2 changed files with 32 additions and 36 deletions

View File

@ -83,7 +83,7 @@ TestCase subclass: MGCPCommandTest [
yourself.
trans command: crcx.
self assert: crcx asDatagram = self exampleCRCX.
self assert: crcx asDatagram equals: self exampleCRCX.
]
exampleRSIP [
@ -99,7 +99,7 @@ TestCase subclass: MGCPCommandTest [
transactionId: '808080';
command: (MGCPOsmoRSIPCommand createRSIP);
yourself.
self assert: trans command asDatagram = self exampleRSIP.
self assert: trans command asDatagram equals: self exampleRSIP.
]
testEndPointName [
@ -107,8 +107,8 @@ TestCase subclass: MGCPCommandTest [
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'.
self assert: (MGCPVirtualTrunk new endpointName: 16rA) equals: 'a@mgw'.
self assert: (trunk endpointName: 16rA) equals: 'ds/e1-1/10@mgw'.
]
testMultiplexTimeslot [
@ -116,14 +116,14 @@ TestCase subclass: MGCPCommandTest [
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: 1) multiplex equals: 0.
self assert: (self trunk endpointAt: 1) timeslot equals: 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.
self assert: (self trunk endpointAt: 31) multiplex equals: 0.
self assert: (self trunk endpointAt: 31) timeslot equals: 31.
self assert: (trunk endpointAt: 1) multiplex = 3.
self assert: (trunk endpointAt: 31) timeslot = 31.
self assert: (trunk endpointAt: 1) multiplex equals: 3.
self assert: (trunk endpointAt: 31) timeslot equals: 31.
]
testMDCXWithSDP [
@ -138,8 +138,7 @@ TestCase subclass: MGCPCommandTest [
yourself.
trans command: mdcx.
mdcx asDatagram printNl.
self assert: mdcx asDatagram = self exampleMDCX.
self assert: mdcx asDatagram equals: self exampleMDCX.
]
tearDown [
@ -238,8 +237,8 @@ TestCase subclass: MGCPTransactionTest [
timeout wait.
self assert: result signals = 0.
self assert: timeout signals = 0.
self assert: result signals equals: 0.
self assert: timeout signals equals: 0.
self assert: self timeoutCallagent sends > 6.
]
@ -261,8 +260,8 @@ TestCase subclass: MGCPTransactionTest [
start.
result wait.
self assert: result signals = 0.
self assert: timeout signals = 0.
self assert: result signals equals: 0.
self assert: timeout signals equals: 0.
self assert: self dropAgent sends >= 2.
]
@ -339,15 +338,15 @@ TestCase subclass: MGCPEndpointAllocTest [
(trunk endpointAt: 20) free.
(trunk endpointAt: 5) free.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '5@mgw'.
self assert: endp endpointName equals: '5@mgw'.
"last_used should be five now"
(trunk endpointAt: 4) free.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '14@mgw'.
self assert: endp endpointName equals: '14@mgw'.
endp := (trunk allocateEndpointIfFailure: []).
self assert: endp endpointName = '4@mgw'.
self assert: endp endpointName equals: '4@mgw'.
]
]
@ -449,11 +448,11 @@ PP.PPCompositeParserTest subclass: MGCPParserTest [
sdp.
res := self parse: inp.
self assert: res code = 200.
self assert: res code equals: 200.
self assert: res isSuccess.
self assert: res transactionId = '32323'.
self assert: res sdp = sdp.
self assert: (res parameterAt: 'I' ifAbsent: []) = '233434'.
self assert: res transactionId equals: '32323'.
self assert: res sdp equals: sdp.
self assert: (res parameterAt: 'I' ifAbsent: []) equals: '233434'.
self assert: res asDatagram equals: inp.
]

View File

@ -60,11 +60,10 @@ PP.PPCompositeParserTest subclass: MGCPGrammarTest [
'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.
self assert: res size equals: 10.
self assert: (res at: 1) equals: 'AUEP'.
self assert: (res at: 3) equals: '23444'.
self assert: (res at: 5) equals: #('13' $@ 'mgw').
]
testReply [
@ -75,9 +74,9 @@ PP.PPCompositeParserTest subclass: MGCPGrammarTest [
res := self parse: '200 123456 OK',
nl.
self assert: res size = 3.
self assert: res first first = '200'.
self assert: res first third = '123456'.
self assert: res size equals: 3.
self assert: res first first equals: '200'.
self assert: res first third equals: '123456'.
]
testReplyByte [
@ -85,10 +84,9 @@ PP.PPCompositeParserTest subclass: MGCPGrammarTest [
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'.
self assert: res size equals: 3.
self assert: res first first equals: '200'.
self assert: res first third equals: '433414656'.
]
testDlcxResponse [
@ -97,6 +95,5 @@ PP.PPCompositeParserTest subclass: MGCPGrammarTest [
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.
]
]