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

SCCP: Work on dispatching the SCCP messages..

This commit is contained in:
Holger Hans Peter Freyther 2010-11-28 21:14:25 +01:00
parent 360e5269b0
commit 300f9f470e
2 changed files with 85 additions and 15 deletions

View File

@ -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
]

View File

@ -25,6 +25,7 @@ Object subclass: IPAConnection [
sccp := SCCPHandler new.
sccp registerOn: dispatcher.
sccp connection: self.
ipa := Osmo.IPAProtoHandler new.
ipa registerOn: dispatcher.