aboutsummaryrefslogtreecommitdiffstats
path: root/SCCPHandler.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-11-29 16:53:00 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-11-29 20:34:22 +0100
commite73c39f5e10dc663230af9f87e9294595a75e609 (patch)
tree47110324d3939bafd7e41fda04bc0cc5ba83ca3e /SCCPHandler.st
parent5a54fe3caf903bfd3fdbce9a3084c6e8ee4736cc (diff)
GSM: Introduce the concept of a 'driver' and a procedure
The procedure holds the driver... everything is still very vague and needs a better design.
Diffstat (limited to 'SCCPHandler.st')
-rw-r--r--SCCPHandler.st86
1 files changed, 45 insertions, 41 deletions
diff --git a/SCCPHandler.st b/SCCPHandler.st
index e7998ff..6ee7b6f 100644
--- a/SCCPHandler.st
+++ b/SCCPHandler.st
@@ -1,7 +1,12 @@
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
- | src dst queue conManager confirmSem proc |
+ | src dst queue conManager confirmSem proc state |
+
+ SCCPConnection class >> stateInitial [ ^ 0 ]
+ SCCPConnection class >> stateConnected [ ^ 1 ]
+ SCCPConnection class >> stateReleased [ ^ 2 ]
+ SCCPConnection class >> stateTimeout [ ^ 3 ]
SCCPConnection class >> new [
^ super new
@@ -9,7 +14,9 @@ Object subclass: SCCPConnection [
]
initialize [
+ state := SCCPConnection stateInitial.
confirmSem := Semaphore new.
+ queue := SharedQueue new.
]
conManager: aHandler [
@@ -19,7 +26,7 @@ Object subclass: SCCPConnection [
readQueue [
<category: 'private'>
- ^ queue ifNil: [ queue := SharedQueue new. ]
+ ^ queue
]
srcRef [
@@ -41,44 +48,44 @@ Object subclass: SCCPConnection [
^ dst
]
- cleanUp [
- "I get called at the end of a SCCP connection"
- <category: 'connection-handling'>
-
- ('Cleaningup the SCCP connection: ', dst asString) printNl.
+ next [
+ "Read the next item. If the connection is terminated"
+ | msg |
- conManager := nil.
- queue := nil.
- proc := nil.
- ]
-
- handleMessages [
- proc := [
- [
- "Wait for the connection or return"
+ "If we are not connected we need to wait"
+ state = SCCPConnection stateInitial
+ ifTrue: [
self waitForConfirmation.
+ ].
- 'SCCP Connection Confirmed' printNl.
+ "If we are not connected here. Send a EndOfStream signal"
+ state = SCCPConnection stateConnected
+ ifFalse: [
+ ^ SystemExceptions.EndOfStream signal
+ ].
- [true] whileTrue: [
- | msg |
+ msg := self readQueue next.
- msg := self readQueue next.
- msg inspect.
- ].
- ] ensure: [
- "An exception? an error?"
- self cleanUp.
- ]
- ] fork.
+ "If this is a small integer our connection is gone"
+ (msg isKindOf: SmallInteger)
+ ifTrue: [
+ ^ SystemExceptions.EndOfStream signal
+ ].
+
+ "We do have a real message"
+ ^ msg
]
+ nextPut: aMsg [
+ 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
].
@@ -86,9 +93,16 @@ Object subclass: SCCPConnection [
^ true
]
+
+ "SCCP Connection state handling"
+ terminate [
+ self readQueue nextPut: 0.
+ ]
+
confirm: aCC [
<category: 'connection-handling'>
self dstRef: aCC src.
+ state := SCCPConnection stateConnected.
confirmSem signal.
]
@@ -100,21 +114,12 @@ Object subclass: SCCPConnection [
| rlc |
"Give up local resources here. We are done."
+ state := SCCPConnection stateReleased.
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
- self sendMsg: rlc toMessage.
+ self nextPut: rlc toMessage.
self terminate.
]
-
- terminate [
- proc ifNotNil: [
- proc terminate.
- ].
- ]
-
- sendMsg: aMsg [
- conManager sendMsg: aMsg.
- ]
]
Object subclass: MSGParser [
@@ -169,7 +174,6 @@ Object subclass: SCCPHandler [
connectionTimeout: aConnection [
('SCCP Connection ', aConnection srcRef asString, ' timeout.') printNl.
- aConnection terminate.
self connections remove: aConnection.
]
@@ -239,9 +243,9 @@ Object subclass: SCCPHandler [
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self connections add: con.
- con handleMessages.
+ self sendMsg: res toMessage.
- ^ res
+ ^ con
]
referenceIsFree: aRef [