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/m2ua/M2UATests.st

223 lines
5.0 KiB
Smalltalk

"
(C) 2013 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/>.
"
Object subclass: M2UAASMock [
| socket |
<category: 'OsmoNetwork-M2UA-Tests'>
<comment: 'A simple mock'>
socketService: aSocket [
<category: 'creation'>
socket := aSocket
]
handleAspActive: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPTM;
msgType: M2UAConstants asptmActivAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspDown: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPSM;
msgType: M2UAConstants aspsmDownAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspInactive: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPTM;
msgType: M2UAConstants asptmInactivAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspUp: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPSM;
msgType: M2UAConstants aspsmUpAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
onData: aData [
| msg |
msg := M2UAMSG parseToClass: aData.
msg dispatchOnAsp: self
]
]
Object subclass: SCTPNetworkServiceMock [
| on_connect on_released on_data as asp |
<category: 'OsmoNetwork-M2UA-Tests'>
<comment: 'I mock SCTPand directly connect an AS with an ASP.'>
onSctpConnect: aBlock [
<category: 'notification'>
on_connect := aBlock
]
applicationServer: anAs [
<category: 'creation'>
as := anAs
]
applicationServerProcess: anAsp [
<category: 'creation'>
asp := anAsp
]
onSctpData: aBlock [
<category: 'creation'>
on_data := aBlock
]
onSctpReleased: aBlock [
<category: 'creation'>
on_released := aBlock
]
hostname [
<category: 'management'>
^'localhost'
]
port [
<category: 'management'>
^0
]
start [
"Nothing"
<category: 'management'>
on_connect value
]
stop [
<category: 'management'>
on_released value
]
nextPut: aMsg [
as onData: aMsg
]
sendToAsp: aMsg [
on_data
value: nil
value: nil
value: 2
value: aMsg
]
]
TestCase subclass: M2UAApplicationServerProcessTest [
<comment: 'A M2UAApplicationServerProcessTest is a test class for testing the behavior of M2UAApplicationServerProcess'>
<category: 'OsmoNetwork-M2UA-Tests'>
testCreation [
| asp |
asp := M2UAApplicationServerProcess new
onAspActive: [];
onAspDown: [];
onAspInactive: [];
onAspUp: [];
onStateChange: [];
onError: [:msg | ];
onNotify: [:type :ident | ];
onSctpEstablished: [];
onSctpReleased: [];
onSctpRestarted: [];
onSctpStatus: [];
yourself
]
testStateTransitions [
| mock as asp |
mock := SCTPNetworkServiceMock new.
as := M2UAASMock new
socketService: mock;
yourself.
asp := M2UAApplicationServerProcess initWith: mock.
mock
applicationServer: as;
applicationServerProcess: asp.
"This works as the mock will handle this synchronously"
self assert: asp state = M2UAAspStateDown.
asp
sctpEstablish;
aspUp.
self assert: asp state = M2UAAspStateInactive.
"Now bring it down and up again"
asp aspDown.
self assert: asp state = M2UAAspStateDown.
asp
aspUp;
aspActive.
self assert: asp state = M2UAAspStateActive.
asp aspDown.
self assert: asp state = M2UAAspStateDown.
asp
aspUp;
aspActive;
aspInactive.
self assert: asp state = M2UAAspStateInactive.
asp sctpRelease.
self assert: asp state = M2UAAspStateDown
]
]
TestCase subclass: M2UAAspStateMachineTest [
<comment: 'A M2UAAspStateMachineTest is a test class for testing the behavior of M2UAAspStateMachine'>
<category: 'OsmoNetwork-M2UA-Tests'>
testLegalTransitions [
| machine |
machine := M2UAAspStateMachine new.
self assert: machine state = M2UAAspStateDown.
machine aspUp: 'Link is up'.
self assert: machine state = M2UAAspStateInactive.
machine aspActive: 'Active'.
self assert: machine state = M2UAAspStateActive.
machine aspInactive: 'Inactive'.
self assert: machine state = M2UAAspStateInactive.
machine aspActive: 'Active'.
self assert: machine state = M2UAAspStateActive.
machine sctpCdi: 'Connection is gone'.
self assert: machine state = M2UAAspStateDown
]
]