summaryrefslogtreecommitdiffstats
path: root/callagent
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-08-10 20:28:59 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-08-10 20:28:59 +0200
commit1a20f003aa5fc7cbeee06db76a9872ea12725ae1 (patch)
tree21d7847a375fdb026f05f75f54615e462aec6465 /callagent
parent1e43d02ed39d926714ee68b213bfbe234f395d1e (diff)
misc: Re-use the parser for a great speed-up during the tests
Creating a PetitParser is expensive due the usage of >>#become: so let us re-use the one from the SIPCallAgent.
Diffstat (limited to 'callagent')
-rw-r--r--callagent/tests/SIPCallAgentTest.st32
-rw-r--r--callagent/tests/SIPInviteTest.st26
-rw-r--r--callagent/tests/SIPRegisterTransactionTest.st6
3 files changed, 32 insertions, 32 deletions
diff --git a/callagent/tests/SIPCallAgentTest.st b/callagent/tests/SIPCallAgentTest.st
index c1d151a..2d6e88c 100644
--- a/callagent/tests/SIPCallAgentTest.st
+++ b/callagent/tests/SIPCallAgentTest.st
@@ -146,7 +146,7 @@ TestCase subclass: SIPCallAgentTest [
call createCall: 'dummy-sdp'.
self assert: call state equals: SIPCall stateInvite.
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: msg class verb equals: SIPInviteRequest verb.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
@@ -162,7 +162,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@@ -183,7 +183,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@@ -195,10 +195,10 @@ TestCase subclass: SIPCallAgentTest [
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
@@ -226,7 +226,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@@ -238,10 +238,10 @@ TestCase subclass: SIPCallAgentTest [
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
@@ -269,7 +269,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
@@ -281,10 +281,10 @@ TestCase subclass: SIPCallAgentTest [
"Verify that a second message has been sent and it contains an auth result"
self assert: sent size equals: 3.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'INVITE'.
secondBranch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
self deny: branch = secondBranch.
@@ -309,7 +309,7 @@ TestCase subclass: SIPCallAgentTest [
"Inject a 200 and check the ACK"
transport inject: (self ok: secondBranch callId: callId tag: fromTag tag cseq: 2).
self assert: sent size equals: 4.
- msg := SIPParser parse: (sent at: 4) data.
+ msg := agent parser parse: (sent at: 4) data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
self assert: call state equals: SIPCall stateSession.
auth := msg parameter: 'Proxy-Authorization' ifAbsent: [nil].
@@ -339,7 +339,7 @@ TestCase subclass: SIPCallAgentTest [
| call msg branch callId fromTag sentNr |
call := self setUpProxyAuthCall.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
callId := (msg parameter: 'Call-ID' ifAbsent: [-1]).
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
@@ -351,7 +351,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: sent size equals: sentNr + 1.
self assert: call state equals: SIPCall stateRemoteHangup.
- msg := SIPParser parse: (sent at: sentNr + 1) data.
+ msg := agent parser parse: (sent at: sentNr + 1) data.
self assert: msg class equals: SIPResponse.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
@@ -365,7 +365,7 @@ TestCase subclass: SIPCallAgentTest [
"First assertions for the invite"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
self assert: call state equals: SIPCall stateInvite.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.
@@ -381,7 +381,7 @@ TestCase subclass: SIPCallAgentTest [
self assert: call state equals: SIPCall stateRedirect.
"Check we get the ACK"
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg class equals: SIPACKRequest.
]
]
diff --git a/callagent/tests/SIPInviteTest.st b/callagent/tests/SIPInviteTest.st
index 4a770aa..a46b50b 100644
--- a/callagent/tests/SIPInviteTest.st
+++ b/callagent/tests/SIPInviteTest.st
@@ -78,7 +78,7 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs isEmpty.
@@ -99,7 +99,7 @@ TestCase subclass: SIPInviteTest [
"Check the reject"
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: msg code equals: '603'.
self assert: msg phrase equals: 'Not Found'.
self assert: agent dialogs size equals: 1.
@@ -110,7 +110,7 @@ TestCase subclass: SIPInviteTest [
transport inject: self createInvite.
self assert: call unregisterDialogIsPending.
self assert: sent size equals: 2.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
secondTag := (msg parameter: 'To' ifAbsent: []) tag.
self assert: firstTag equals: secondTag.
]
@@ -130,20 +130,20 @@ TestCase subclass: SIPInviteTest [
"Check the messages"
self assert: sent size equals: 3.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
tag := (msg parameter: 'To' ifAbsent: []) tag.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
self assert: agent dialogs size equals: 1.
self deny: call unregisterDialogIsPending.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
self assert: agent dialogs size equals: 1.
@@ -161,7 +161,7 @@ TestCase subclass: SIPInviteTest [
"Now hangup the call"
call hangup.
self assert: call state equals: call class stateHangup.
- msg := SIPParser parse: sent fourth data.
+ msg := agent parser parse: sent fourth data.
self assert: msg class equals: SIPByeRequest.
]
@@ -180,14 +180,14 @@ TestCase subclass: SIPInviteTest [
"Send a 100 Trying to the other end"
call trying.
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
"Retransmit the INVITE to forc another trying"
transport inject: self createInvite.
self assert: sent size equals: 2.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg code equals: '100'.
self assert: msg phrase equals: 'Trying'.
@@ -195,13 +195,13 @@ TestCase subclass: SIPInviteTest [
"Now ring and re-transmit"
call ringing.
self assert: sent size equals: 3.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
transport inject: self createInvite.
self assert: sent size equals: 4.
- msg := SIPParser parse: (sent at: 4) data.
+ msg := agent parser parse: (sent at: 4) data.
self assert: msg code equals: '180'.
self assert: msg phrase equals: 'Ringing'.
@@ -209,13 +209,13 @@ TestCase subclass: SIPInviteTest [
"Now pick-up..."
call pickUp: 'file'.
self assert: sent size equals: 5.
- msg := SIPParser parse: (sent at: 5) data.
+ msg := agent parser parse: (sent at: 5) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
transport inject: self createInvite.
self assert: sent size equals: 6.
- msg := SIPParser parse: (sent at: 6) data.
+ msg := agent parser parse: (sent at: 6) data.
self assert: msg code equals: '200'.
self assert: msg phrase equals: 'OK'.
]
diff --git a/callagent/tests/SIPRegisterTransactionTest.st b/callagent/tests/SIPRegisterTransactionTest.st
index cdb1542..fcc239b 100644
--- a/callagent/tests/SIPRegisterTransactionTest.st
+++ b/callagent/tests/SIPRegisterTransactionTest.st
@@ -74,7 +74,7 @@ TestCase subclass: SIPRegisterTransactionTest [
yourself.
register start.
self assert: sent size equals: 1.
- msg := SIPParser parse: sent first data.
+ msg := agent parser parse: sent first data.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 1.
"Now inject an auth requirement message"
@@ -83,10 +83,10 @@ TestCase subclass: SIPRegisterTransactionTest [
fromTag := (msg parameter: 'From' ifAbsent: [nil]).
transport inject: (self createSimple401: branch callId: callId tag: fromTag tag cseq: 1).
self assert: sent size equals: 3.
- msg := SIPParser parse: sent second data.
+ msg := agent parser parse: sent second data.
self assert: msg class verb equals: 'ACK'.
- msg := SIPParser parse: sent third data.
+ msg := agent parser parse: sent third data.
self assert: msg class verb equals: 'REGISTER'.
self assert: (msg parameter: 'CSeq' ifAbsent: [-1]) number equals: 2.
branch := (msg parameter: 'Via' ifAbsent: [nil]) branch.