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

sccp: Create a SCCPConnection on a handler, then open it

Change the way a SCCPConnection is created, this way the connection
only registers with the handler to get a srcRef generated and then
can open the connection.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-15 21:17:58 +02:00
parent f4f6563254
commit 61ed86368d
2 changed files with 29 additions and 22 deletions

View File

@ -28,8 +28,22 @@ Object subclass: SCCPConnectionBase [
SCCPConnectionBase class >> stateTimeout [ ^ 3 ]
SCCPConnectionBase class >> new [
^ self shouldNotImplement
]
SCCPConnectionBase class >> on: aHandler [
^ super new
initialize; yourself
initialize;
conManager: aHandler;
yourself
]
connectionRequest: aData [
| res |
"Send the confirmation now"
res := Osmo.SCCPConnectionRequest
initWith: (self srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self nextPut: res toMessage.
]
initialize [
@ -44,7 +58,14 @@ Object subclass: SCCPConnectionBase [
conManager: aHandler [
<category: 'private'>
"Check if it is not there otherwise bad things happen"
conManager ifNotNil: [
^ self error: 'Can only be set once.'.
].
conManager := aHandler.
conManager addConnection: self
]
srcRef [
@ -289,11 +310,10 @@ Object subclass: SCCPHandler [
confirmConnection: aMsg [
| con res |
con := self connectionSpecies new.
con conManager: self.
self addConnection: con.
"Confirm the messga now and send any data"
con := self connectionSpecies on: self.
"Confirm the message now and send any data"
con confirm: aMsg.
aMsg data ifNotNil: [
con data: aMsg.
@ -335,21 +355,6 @@ Object subclass: SCCPHandler [
connection send: aMsg with: Osmo.IPAConstants protocolSCCP.
]
createConnection: aData [
| con res|
con := self connectionSpecies new.
con conManager: self.
self addConnection: con.
"Send the confirmation now"
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self sendMsg: res toMessage.
^ con
]
referenceIsFree: aRef [
<category: 'private'>
self connections do: [:each |

View File

@ -510,7 +510,8 @@ TestCase subclass: SCCPHandlerTest [
handler := SCCPHandlerNonRec new.
handler connection: DummyConnection new.
con := handler createConnection: '123' asByteArray.
con := SCCPMockConnection on: handler.
con connectionRequest: '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.
@ -539,7 +540,8 @@ TestCase subclass: SCCPHandlerTest [
server connection: (DirectConnection initWith: client).
"Establish the connection"
con := client createConnection: '123' asByteArray.
con := SCCPMockConnection on: client.
con connectionRequest: '123' asByteArray.
self assert: con state = SCCPConnection stateConnected.
self assert: server connections size = 1.