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

sccp: Remove the blocking interface from the SCCP code.

This commit is contained in:
Holger Hans Peter Freyther 2011-06-15 18:39:05 +02:00
parent 0c55cb053c
commit f4f6563254
2 changed files with 57 additions and 72 deletions

View File

@ -18,24 +18,23 @@
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
| src dst queue conManager confirmSem proc state |
Object subclass: SCCPConnectionBase [
| src dst conManager confirmSem proc state |
SCCPConnection class >> stateInitial [ ^ 0 ]
SCCPConnection class >> stateConnected [ ^ 1 ]
SCCPConnection class >> stateReleased [ ^ 2 ]
SCCPConnection class >> stateReleaseComplete [ ^ 3 ]
SCCPConnection class >> stateTimeout [ ^ 3 ]
SCCPConnectionBase class >> stateInitial [ ^ 0 ]
SCCPConnectionBase class >> stateConnected [ ^ 1 ]
SCCPConnectionBase class >> stateReleased [ ^ 2 ]
SCCPConnectionBase class >> stateReleaseComplete [ ^ 3 ]
SCCPConnectionBase class >> stateTimeout [ ^ 3 ]
SCCPConnection class >> new [
SCCPConnectionBase class >> new [
^ super new
initialize; yourself
]
initialize [
state := SCCPConnection stateInitial.
state := self class stateInitial.
confirmSem := Semaphore new.
queue := SharedQueue new.
]
conManager [
@ -48,11 +47,6 @@ Object subclass: SCCPConnection [
conManager := aHandler.
]
readQueue [
<category: 'private'>
^ queue
]
srcRef [
<category: 'access'>
^ src
@ -72,34 +66,6 @@ Object subclass: SCCPConnection [
^ dst
]
next [
"Read the next item. If the connection is terminated"
| msg |
"If we are not connected we need to wait"
state = SCCPConnection stateInitial
ifTrue: [
self waitForConfirmation.
].
"If we are not connected here. Send a EndOfStream signal"
(state > SCCPConnection stateConnected and: [self readQueue isEmpty])
ifTrue: [
^ SystemExceptions.EndOfStream signal
].
msg := self readQueue next.
"If this is a small integer our connection is gone"
(msg isKindOf: SmallInteger)
ifTrue: [
^ SystemExceptions.EndOfStream signal
].
"We do have a real message"
^ msg
]
nextPutData: aMsg [
| dt1 |
dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg.
@ -110,47 +76,24 @@ Object subclass: SCCPConnection [
conManager sendMsg: aMsg.
]
waitForConfirmation [
"Wait for the connection to be confirmed and then exit"
((Delay forSeconds: 10) timedWaitOn: confirmSem)
ifTrue: [
state := SCCPConnection stateTimeout.
conManager connectionTimeout: self.
^ false
].
^ true
]
"SCCP Connection state handling"
terminate [
self readQueue nextPut: 0.
]
confirm: aCC [
<category: 'connection-handling'>
self dstRef: aCC src.
state := SCCPConnection stateConnected.
state := self class stateConnected.
confirmSem signal.
]
data: aDT [
self readQueue nextPut: aDT data.
]
release [
| rlsd |
state := SCCPConnection stateReleased.
state := self class 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"
state := SCCPConnection stateReleaseComplete.
state := self class stateReleaseComplete.
self terminate.
]
@ -158,7 +101,7 @@ Object subclass: SCCPConnection [
| rlc |
"Give up local resources here. We are done."
state := SCCPConnection stateReleaseComplete.
state := self class stateReleaseComplete.
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
@ -168,6 +111,16 @@ Object subclass: SCCPConnection [
state [ <category: 'accessing'> ^ state ]
]
SCCPConnectionBase subclass: SCCPConnection [
data: aDT [
"nothing implemented"
]
terminate [
"noting implemented"
]
]
Object subclass: MSGParser [
<comment: 'I take a SCCP message and recursively parse all the data'>
@ -330,9 +283,13 @@ Object subclass: SCCPHandler [
"Interesting for subclasses"
]
connectionSpecies [
^ SCCPConnection
]
confirmConnection: aMsg [
| con res |
con := SCCPConnection new.
con := self connectionSpecies new.
con conManager: self.
self addConnection: con.
@ -381,7 +338,7 @@ Object subclass: SCCPHandler [
createConnection: aData [
| con res|
con := SCCPConnection new.
con := self connectionSpecies new.
con conManager: self.
self addConnection: con.

View File

@ -465,8 +465,36 @@ Object subclass: DirectConnection [
]
]
SCCPConnection subclass: SCCPMockConnection [
| queue |
readQueue [ ^ queue ifNil: [queue := SharedQueue new]]
next [
| res |
res := queue next.
res = 0 ifTrue: [
^ SystemExceptions.EndOfStream signal
].
^ res
]
data: aDT [
self readQueue nextPut: aDT data
]
terminate [
self readQueue nextPut: 0
]
]
SCCPHandler subclass: SCCPHandlerNonRec [
connectionSpecies [
^ SCCPMockConnection
]
dissectMSG: aMsg [
^ Osmo.SCCPMessage decode: aMsg asByteArray.
]