smalltalk
/
osmo-st-all
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-all/osmo-st-network/ipa/IPATests.st

161 lines
5.6 KiB
Smalltalk

"
(C) 2010-2012 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: IPATests [
| called |
<category: 'OsmoNetwork-Tests'>
IPATests class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('OsmoNetwork')
]
testMux [
| data mux |
mux := IPAMuxer new.
data := {
{mux prepareNext: #(1 2 3) with: IPAConstants protocolOML.
#(0 3 255 1 2 3) asByteArray}.
{mux prepareNext: #(1 2 3) with: IPAConstants protocolOsmoMGCP.
#(0 4 238 1 1 2 3) asByteArray}.
}.
data do: [:each |
self assert: each first = each second.]
]
testDispatch [
| dispatch |
<category: 'dispatch-test'>
called := false.
dispatch := IPADispatcher new
addHandler: 16r23 on: self with: #dispatchcallback:;
yourself.
dispatch dispatch: 16r23 with: 'data'.
self assert: called.
called := false.
dispatch
addHandler: 16r42 on: [:msg | called := msg = 'data' ];
dispatch: 16r42 with: 'data'.
self assert: called.
]
dispatchcallback: aData [
<category: 'dispatch-test'>
called := aData = 'data'.
]
]
TestCase subclass: IPAMsgTests [
<category: 'OsmoNetwork-Tests'>
IPAMsgTests class >> parseOnlyData [
^ Array
with: IPAMsgResponse->#(16r05 16r00 16r0A 16r08 16r31 16r38 16r30 16r31
16r2F 16r30 16r2F 16r30 16r00 16r00 16r13 16r07
16r30 16r30 16r3A 16r30 16r32 16r3A 16r39 16r35
16r3A 16r30 16r30 16r3A 16r34 16r30 16r3A 16r36
16r34 16r00 16r00 16r02 16r02 16r00 16r00 16r0D
16r03 16r42 16r54 16r53 16r5F 16r4E 16r42 16r54
16r31 16r33 16r31 16r47 16r00 16r00 16r0C 16r04
16r31 16r36 16r35 16r61 16r30 16r32 16r39 16r5F
16r35 16r35 16r00 16r00 16r14 16r05 16r31 16r36
16r38 16r64 16r34 16r37 16r32 16r5F 16r76 16r32
16r30 16r30 16r62 16r31 16r34 16r33 16r64 16r30
16r00 16r00 16r18 16r01 16r6E 16r62 16r74 16r73
16r2D 16r30 16r30 16r2D 16r30 16r32 16r2D 16r39
16r35 16r2D 16r30 16r30 16r2D 16r34 16r30 16r2D
16r36 16r34 16r00 16r00 16r0A 16r00 16r30 16r30
16r31 16r30 16r32 16r37 16r32 16r39 16r00).
]
IPAMsgTests class >> data [
<category: 'test-data'>
^ Array
with: IPAMsgRequest->#(16r04 16r01 16r08 16r01 16r07 16r01 16r02 16r01
16r03 16r01 16r04 16r01 16r05 16r01 16r01 16r01
16r00)
with: IPAMsgResponse->#(16r05 16r00 16r04 16r01 16r31 16r38 16r30 16r31)
]
testMsgDissect [
self class data do: [:test_data | | msg stream |
stream := test_data value readStream.
msg := test_data key parse: stream.
self
assert: stream atEnd;
assert: msg toMessage asByteArray = test_data value asByteArray;
should: [msg dataForTag: 9] raise: SystemExceptions.NotFound;
deny: (msg hasTag: 9).
]
]
testMsgInputStrict [
| test_data msg stream |
test_data := self class data first.
stream := test_data value readStream.
msg := test_data key parse: stream.
self
assert: stream atEnd;
assert: msg tags = #(8 7 2 3 4 5 1 0) asOrderedCollection;
assert: (msg hasTag: 8);
assert: (msg dataForTag: 8) = nil.
]
testParseOnly [
"This tests that parsing a 'malformed' response will actually
work, generating the response will be different though."
self class parseOnlyData do: [:test_data | | msg stream |
stream := test_data value readStream.
msg := test_data key parse: stream.
self
assert: stream atEnd;
assert: (msg hasTag: 16r0);
assert: (msg hasTag: 16r1);
assert: (msg hasTag: 16r2);
assert: (msg hasTag: 16r3);
assert: (msg hasTag: 16r4);
assert: (msg hasTag: 16r5);
assert: (msg hasTag: 16r7);
assert: (msg hasTag: 16r8);
deny: (msg hasTag: 16rA);
assert: (msg dataForTag: 16r0) = #(16r30 16r30 16r31 16r30 16r32 16r37 16r32 16r39 16r0) asByteArray.
]
]
]
TestCase subclass: IPAGSTTests [
<category: 'OsmoNetwork-Tests'>
testSize [
self assert: IPASCCPState sizeof = 25.
]
]