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

113 lines
2.5 KiB
Smalltalk
Raw Normal View History

2010-11-14 21:43:29 +00:00
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
| src dst queue |
srcRef [
^ src
]
srcRef: aRef [
src := aRef
]
dstRef: aRef [
dst := aRef
]
enqueueForRead: aMsg [
self queue next: aMsg.
]
readQueue [
^ queue ifNil: [ queue := SharedQueue new. ]
]
]
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 |
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
]
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.
]
2010-11-14 21:43:29 +00:00
]
createConnection: aData [
| con res|
con := SCCPConnection new.
con srcRef: self assignSrcRef.
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self connections add: con.
^ res
]
assignSrcRef [
^ 666
]
connections [
^ connections ifNil: [ connections := OrderedCollection new. ]
]
2010-11-14 21:43:29 +00:00
]