aboutsummaryrefslogtreecommitdiffstats
path: root/SCCPHandler.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-11-28 21:14:25 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-11-28 21:27:58 +0100
commit300f9f470e087d095513220bd83a5bf8548418de (patch)
tree4f1d23867aacc50e76bc9864610bfe92a410030e /SCCPHandler.st
parent360e5269b0b78802b95cbdfaa4d724ee1d032edb (diff)
SCCP: Work on dispatching the SCCP messages..
Diffstat (limited to 'SCCPHandler.st')
-rw-r--r--SCCPHandler.st99
1 files changed, 84 insertions, 15 deletions
diff --git a/SCCPHandler.st b/SCCPHandler.st
index 777ec2f..0566eaa 100644
--- a/SCCPHandler.st
+++ b/SCCPHandler.st
@@ -1,44 +1,106 @@
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
- | src dst queue |
+ | src dst queue handler confirmSem proc |
+
+ SCCPConnection class >> new [
+ ^ super new
+ initialize; yourself
+ ]
+
+ initialize [
+ confirmSem := Semaphore new.
+ ]
+
+ handler: aHandler [
+ <category: 'private'>
+ handler := aHandler.
+ ]
srcRef [
+ <category: 'access'>
^ src
]
srcRef: aRef [
+ <category: 'access'>
src := aRef
]
dstRef: aRef [
+ <category: 'access'>
dst := aRef
]
dstRef [
+ <category: 'access'>
^ dst
]
- enqueueForRead: aMsg [
- self queue next: aMsg.
- ]
-
readQueue [
^ queue ifNil: [ queue := SharedQueue new. ]
]
+ cleanUp [
+ "I get called at the end of a SCCP connection"
+ <category: 'connection-handling'>
+
+ ('Cleaningup the SCCP connection: ', dst asString) printNl.
+
+ handler := nil.
+ queue := nil.
+ proc := nil.
+ ]
+
+ handleMessages [
+ proc := [
+ [
+ self waitForConfirmation.
+ 'SCCP Connection Confirmed' printNl.
+
+ [true] whileTrue: [
+ | msg |
+
+ msg := self readQueue next.
+ msg inspect.
+ ].
+ ] ensure: [
+ "An exception? an error?"
+ self cleanUp.
+ ]
+ ] fork.
+ ]
+
+
+ waitForConfirmation [
+ "TODO: Add timeout handling"
+ confirmSem wait
+ ]
+
confirm: aCC [
<category: 'connection-handling'>
- 'Confirm' printNl.
- self srcRef: aCC dst.
+ self dstRef: aCC src.
+ confirmSem signal.
]
data: aDT [
- 'Got data' printNl.
+ self readQueue nextPut: aDT data.
]
released: aRLSD [
+ | rlc |
"Give up local resources here. We are done."
- 'Connection got released...' printNl.
+
+ rlc := Osmo.SCCPConnectionReleaseComplete
+ initWithDst: aRLSD src src: aRLSD dst.
+ self sendMsg: rlc toMessage.
+
+ proc ifNotNil: [
+ proc terminate.
+ ]
+ ]
+
+ sendMsg: aMsg [
+ handler sendMsg: aMsg.
]
]
@@ -84,7 +146,7 @@ Object subclass: MSGParser [
]
Object subclass: SCCPHandler [
- | connections last_ref |
+ | connections last_ref connection |
<comment: 'I handle SCCP messages'>
registerOn: aDispatcher [
@@ -128,13 +190,8 @@ Object subclass: SCCPHandler [
handleMsg: aMsg [
| sccp |
- 'Got a new SCCP message here.' printNl.
-
[
sccp := MSGParser parse: (aMsg asByteArray).
- sccp inspect.
- sccp printNl.
- sccp class printNl.
] on: Exception do: [
self logError: 'Failed to parse message' area: #sccp.
aMsg asByteArray printNl.
@@ -144,14 +201,26 @@ Object subclass: SCCPHandler [
self dispatchMessage: sccp.
]
+
+ connection: aConnection [
+ connection := aConnection.
+ ]
+
+ sendMsg: aMsg [
+ "Send a SCCP message."
+ connection send: aMsg with: Osmo.IPAConstants protocolSCCP.
+ ]
+
createConnection: aData [
| con res|
con := SCCPConnection new.
con srcRef: self assignSrcRef.
+ con handler: self.
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self connections add: con.
+ con handleMessages.
^ res
]