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

SCCPHandler: Make sure that we drain all messages.

This commit is contained in:
Holger Hans Peter Freyther 2010-12-15 16:24:45 +01:00
parent 3993a4307e
commit 912ff78f55
3 changed files with 37 additions and 2 deletions

View File

@ -77,8 +77,8 @@ Object subclass: SCCPConnection [
].
"If we are not connected here. Send a EndOfStream signal"
state = SCCPConnection stateConnected
ifFalse: [
(state > SCCPConnection stateConnected and: [self readQueue isEmpty])
ifTrue: [
^ SystemExceptions.EndOfStream signal
].

View File

@ -426,3 +426,37 @@ TestCase subclass: TestMessages [
self assert: msg toMessage asByteArray = inp.
]
]
Object subclass: DummyConnection [
send: aMsg with: aProto [
"NOP"
]
]
SCCPHandler subclass: SCCPHandlerNonRec [
handleMsg: aMsg [
self dispatchMessage: (Osmo.SCCPMessage decode: aMsg asByteArray).
]
]
TestCase subclass: SCCPHandlerTest [
<comment: 'Test that one can do easy connection handling'>
testDisconnectWithMSG [
| handler con amount result |
"This should test that we process all pending data in a socket"
handler := SCCPHandlerNonRec new.
handler connection: DummyConnection new.
con := handler createConnection: '123' asByteArray.
handler handleMsg: (Osmo.SCCPConnectionConfirm initWithSrc: 567 dst: con srcRef) toMessage asByteArray.
handler handleMsg: (Osmo.SCCPConnectionData initWith: con srcRef data: '123' asByteArray) toMessage asByteArray.
handler handleMsg: (Osmo.SCCPConnectionReleased initWithDst: con srcRef src: 567 cause: 16rFE) toMessage asByteArray.
self shouldnt: [con next] raise: SystemExceptions.EndOfStream description: 'Should read the 123'.
self should: [con next] raise: SystemExceptions.EndOfStream description: 'Now we should be at the end'.
]
]

View File

@ -15,6 +15,7 @@
<sunit>OsmoGSM.BSSAPTest</sunit>
<sunit>OsmoGSM.GSM48Test</sunit>
<sunit>OsmoGSM.TestMessages</sunit>
<sunit>OsmoGSM.SCCPHandlerTest</sunit>
<filein>Tests.st</filein>
</test>