smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-gsm/SCCPHandler.st

237 lines
5.3 KiB
Smalltalk
Raw Normal View History

2010-11-14 21:43:29 +00:00
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
| 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
]
2010-11-28 09:14:15 +00:00
dstRef [
<category: 'access'>
2010-11-28 09:14:15 +00:00
^ dst
]
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'>
self dstRef: aCC src.
confirmSem signal.
]
data: aDT [
self readQueue nextPut: aDT data.
]
released: aRLSD [
| rlc |
"Give up local resources here. We are done."
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self sendMsg: rlc toMessage.
proc ifNotNil: [
proc terminate.
]
]
sendMsg: aMsg [
handler sendMsg: aMsg.
]
]
Object subclass: MSGParser [
<comment: 'I take a SCCP message and recursively parse all the data'>
MSGParser class >> parse: aByteArray [
| sccp |
"Return a completely decoded subtree"
sccp := Osmo.SCCPMessage decode: aByteArray.
(sccp respondsTo: #data)
ifTrue: [
sccp data: (self decodeBSSAP: sccp data).
].
^ sccp
]
MSGParser class >> decodeBSSAP: aData [
| bssap |
bssap := BSSAPMessage decode: aData.
2010-11-24 14:17:10 +00:00
bssap class msgType = BSSAPDTAP msgType
ifTrue: [
2010-11-24 14:17:10 +00:00
bssap data: (GSM48MSG decode: bssap data)
]
ifFalse: [
bssap data: (self decodeBSSMAP: bssap data).
2010-11-24 14:17:10 +00:00
].
^ bssap
]
MSGParser class >> decodeBSSMAP: aData [
| bssmap |
bssmap := IEMessage decode: aData with: GSM0808IE.
bssmap findIE: (GSMLayer3Info elementId) ifPresent: [:each |
each data: (GSM48MSG decode: each data).
].
^ bssmap
]
]
Object subclass: SCCPHandler [
| connections last_ref connection |
2010-11-14 21:43:29 +00:00
<comment: 'I handle SCCP messages'>
registerOn: aDispatcher [
aDispatcher addHandler: Osmo.IPAConstants protocolSCCP
on: self with: #handleMsg:.
2010-11-14 21:43:29 +00:00
]
forwardMessage: aMessage with: aConnection[
(aMessage isKindOf: Osmo.SCCPConnectionConfirm)
ifTrue: [
aConnection confirm: aMessage.
^ true
].
(aMessage isKindOf: Osmo.SCCPConnectionData)
ifTrue: [
aConnection data: aMessage.
^ true
].
(aMessage isKindOf: Osmo.SCCPConnectionReleased)
ifTrue: [
aConnection released: aMessage.
self connections remove: aConnection.
^ true
].
"Message is not handled here"
^ false
]
2010-11-28 09:14:15 +00:00
dispatchMessage: aMessage [
self connections do: [:each |
each srcRef = aMessage dst
2010-11-28 09:14:15 +00:00
ifTrue: [
^ self forwardMessage: aMessage with: each.
2010-11-28 09:14:15 +00:00
].
].
'No one has handled the connection with ', aMessage dst asString printNl.
2010-11-28 09:14:15 +00:00
]
handleMsg: aMsg [
| sccp |
[
sccp := MSGParser parse: (aMsg asByteArray).
] on: Exception do: [
self logError: 'Failed to parse message' area: #sccp.
aMsg asByteArray printNl.
2010-11-28 09:14:15 +00:00
^ false
].
self dispatchMessage: sccp.
2010-11-14 21:43:29 +00:00
]
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
]
assignSrcRef [
^ 666
]
connections [
^ connections ifNil: [ connections := OrderedCollection new. ]
]
2010-11-14 21:43:29 +00:00
]