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

306 lines
7.6 KiB
Smalltalk
Raw Normal View History

2010-12-14 02:03:20 +00:00
"
(C) 2010 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
2010-11-14 21:43:29 +00:00
PackageLoader fileInPackage: 'OsmoNetwork'.
Object subclass: SCCPConnection [
| 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
initialize; yourself
]
initialize [
state := SCCPConnection stateInitial.
confirmSem := Semaphore new.
queue := SharedQueue new.
]
conManager: aHandler [
<category: 'private'>
conManager := aHandler.
]
readQueue [
<category: 'private'>
^ queue
]
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
]
next [
"Read the next item. If the connection is terminated"
| msg |
"If we are not connected we need to wait"
state = SCCPConnection stateInitial
ifTrue: [
self waitForConfirmation.
].
"If we are not connected here. Send a EndOfStream signal"
(state > SCCPConnection stateConnected and: [self readQueue isEmpty])
ifTrue: [
^ SystemExceptions.EndOfStream signal
].
msg := self readQueue next.
"If this is a small integer our connection is gone"
(msg isKindOf: SmallInteger)
ifTrue: [
^ SystemExceptions.EndOfStream signal
].
"We do have a real message"
^ msg
]
nextPutData: aMsg [
| dt1 |
dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg.
self nextPut: dt1 toMessage.
]
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
].
^ true
]
"SCCP Connection state handling"
terminate [
self readQueue nextPut: 0.
]
confirm: aCC [
<category: 'connection-handling'>
self dstRef: aCC src.
state := SCCPConnection stateConnected.
confirmSem signal.
]
data: aDT [
self readQueue nextPut: aDT data.
]
released: aRLSD [
| rlc |
"Give up local resources here. We are done."
state := SCCPConnection stateReleased.
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
self terminate.
]
]
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
]
connectionTimeout: aConnection [
('SCCP Connection ', aConnection srcRef asString, ' timeout.') printNl.
self connections remove: aConnection.
]
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 toMessageOrByteArray 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 conManager: self.
res := Osmo.SCCPConnectionRequest
initWith: (con srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self connections add: con.
self sendMsg: res toMessage.
^ con
]
referenceIsFree: aRef [
<category: 'private'>
self connections do: [:each |
each srcRef = aRef
ifTrue: [
^ false
].
].
^ true
]
assignSrcRef [
"Find a free SCCP reference"
1 to: 16rFFFFFE do: [:dummy |
| ref |
ref := Random between: 1 and: 16rFFFFFE.
(self referenceIsFree: ref)
ifTrue: [
^ ref.
].
].
self error: 'No free SCCP Connection. Close some'.
]
connections [
^ connections ifNil: [ connections := OrderedCollection new. ]
]
2010-11-14 21:43:29 +00:00
]