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

sccp: Work on accepting connections and releasing them.

This commit is contained in:
Holger Hans Peter Freyther 2010-12-16 21:10:20 +01:00
parent 22252d43b7
commit 198eaba529
2 changed files with 110 additions and 3 deletions

View File

@ -134,6 +134,19 @@ Object subclass: SCCPConnection [
self readQueue nextPut: aDT data.
]
release [
| rlsd |
state := SCCPConnection stateReleased.
rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0.
self nextPut: rlsd toMessage.
]
releaseComplete: aMSG [
"TODO: verify that we are in the right state"
self terminate.
]
released: aRLSD [
| rlc |
"Give up local resources here. We are done."
@ -144,6 +157,8 @@ Object subclass: SCCPConnection [
self nextPut: rlc toMessage.
self terminate.
]
state [ <category: 'accessing'> ^ state ]
]
Object subclass: MSGParser [
@ -218,6 +233,14 @@ Object subclass: SCCPHandler [
self connections remove: aConnection.
^ true
].
(aMessage isKindOf: Osmo.SCCPConnectionReleaseComplete)
ifTrue: [
aConnection releaseComplete: aMessage.
self connections remove: aConnection.
^ true.
].
self logError: 'Unhandled SCCP packet %1' % {aMessage class} area: #sccp.
"Message is not handled here"
^ false
@ -234,17 +257,52 @@ Object subclass: SCCPHandler [
'No one has handled the connection with ', aMessage dst asString printNl.
]
dissectMSG: aMsg [
^ MSGParser parse: (aMsg asByteArray).
]
newConnection: aCon [
"Interesting for subclasses"
]
confirmConnection: aMsg [
| con res |
con := SCCPConnection new.
con srcRef: self assignSrcRef.
con conManager: self.
self connections add: con.
"Confirm the messga now and send any data"
con confirm: aMsg.
aMsg data ifNotNil: [
con data: aMsg.
].
"Confirm it without sending any new data bad"
res := Osmo.SCCPConnectionConfirm initWithSrc: (con srcRef) dst: (con dstRef).
self sendMsg: res toMessage.
self newConnection: con.
^ con.
]
handleMsg: aMsg [
| sccp |
[
sccp := MSGParser parse: (aMsg asByteArray).
sccp := self dissectMSG: aMsg asByteArray.
] on: Exception do: [
self logError: 'Failed to parse message' area: #sccp.
aMsg toMessageOrByteArray printNl.
^ false
].
(sccp isKindOf: Osmo.SCCPConnectionRequest) ifTrue: [
self logNotice: 'New incoming connection' area: #sccp.
self confirmConnection: sccp.
^ true
].
self dispatchMessage: sccp.
]

View File

@ -433,10 +433,23 @@ Object subclass: DummyConnection [
]
]
Object subclass: DirectConnection [
| handler |
DirectConnection class >> initWith: aHandler [
^ self new
instVarNamed: #handler put: aHandler; yourself.
]
send: aMsg with: aProto [
handler handleMsg: aMsg.
]
]
SCCPHandler subclass: SCCPHandlerNonRec [
handleMsg: aMsg [
self dispatchMessage: (Osmo.SCCPMessage decode: aMsg asByteArray).
dissectMSG: aMsg [
^ Osmo.SCCPMessage decode: aMsg asByteArray.
]
]
@ -466,4 +479,40 @@ TestCase subclass: SCCPHandlerTest [
handler handleMsg: (Osmo.SCCPConnectionData initWith: con srcRef data: '123' asByteArray) toMessage asByteArray.
self assert: con readQueue isEmpty.
]
testConnectionHandling [
| client server con serverCon|
"Test opening and closing connections"
client := SCCPHandlerNonRec new.
server := SCCPHandlerNonRec new.
"Connect both handlers directly"
client connection: (DirectConnection initWith: server).
server connection: (DirectConnection initWith: client).
"Establish the connection"
con := client createConnection: '123' asByteArray.
self assert: con state = SCCPConnection stateConnected.
self assert: server connections size = 1.
serverCon := server connections first.
self assert: serverCon state = SCCPConnection stateConnected.
"Check if we were able to read data"
self assert: serverCon readQueue isEmpty not.
self assert: serverCon next = '123' asByteArray.
"Now close the connection"
serverCon release.
self assert: serverCon state = SCCPConnection stateReleased.
self assert: con state = SCCPConnection stateReleased.
self assert: client connections size = 0.
self assert: server connections size = 0.
"Verify we will now get exceptions"
self should: [con next] raise: SystemExceptions.EndOfStream.
self should: [serverCon next] raise: SystemExceptions.EndOfStream.
]
]