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

459 lines
11 KiB
Smalltalk
Raw Normal View History

2010-12-14 02:03:20 +00:00
"
(C) 2010-2011 by Holger Hans Peter Freyther
2010-12-14 02:03:20 +00:00
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: SCCPConnectionBase [
| src dst conManager confirmSem proc state sem |
SCCPConnectionBase class >> stateInitial [ <category: 'state'> ^ 0 ]
SCCPConnectionBase class >> stateRequested [ <category: 'state'> ^ 1 ]
SCCPConnectionBase class >> stateConnected [ <category: 'state'> ^ 2 ]
SCCPConnectionBase class >> stateReleased [ <category: 'state'> ^ 3 ]
SCCPConnectionBase class >> stateReleaseComplete [ <category: 'state'> ^ 4 ]
SCCPConnectionBase class >> stateTimeout [ <category: 'state'> ^ 5 ]
SCCPConnectionBase class >> new [
<category: 'creation'>
^ self shouldNotImplement
]
SCCPConnectionBase class >> on: aHandler [
<category: 'creation'>
^ super new
initialize;
conManager: aHandler;
yourself
]
initialize [
<category: 'creation'>
state := self class stateInitial.
confirmSem := Semaphore new.
sem := RecursionLock new.
]
conManager: aHandler [
<category: 'creation'>
"Check if it is not there otherwise bad things happen"
conManager ifNotNil: [
^ self error: 'Can only be set once.'.
].
conManager := aHandler.
conManager addConnection: self
]
state [ <category: 'accessing'>
^ state
]
conManager [
<category: 'accessing'>
^ conManager
]
srcRef [
<category: 'accessing'>
^ src
]
srcRef: aRef [
<category: 'accessing'>
src := aRef
]
dstRef: aRef [
<category: 'accessing'>
dst := aRef
]
2010-11-28 09:14:15 +00:00
dstRef [
<category: 'accessing'>
2010-11-28 09:14:15 +00:00
^ dst
]
changeState: newState do: aBlock [
sem critical: [
state := newState.
aBlock value
]
]
connectionRequest: aData [
| res |
<category: 'handling'>
"Send the confirmation now"
self changeState: self class stateRequested do: [
res := Osmo.SCCPConnectionRequest
initWith: (self srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self nextPut: res toMessage.
].
]
confirm: aCC [
<category: 'handling'>
self changeState: self class stateConnected do: [
self dstRef: aCC src.
confirmSem signal.
]
]
release [
| rlsd |
<category: 'handling'>
self changeState: self class stateReleased do: [
rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0.
self nextPut: rlsd toMessage.
]
]
releaseComplete: aMSG [
<category: 'handling'>
"TODO: verify that we are in the right state"
self changeState: self class stateReleaseComplete do: [
self terminate.
]
]
released: aRLSD [
| rlc |
<category: 'handling'>
"Give up local resources here. We are done."
self changeState: self class stateReleaseComplete do: [
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
self terminate.
]
]
nextPutData: aMsg [
| dt1 |
<category: 'output'>
dt1 := Osmo.SCCPConnectionData initWith: self dstRef data: aMsg.
sem critical: [self nextPut: dt1 toMessage].
]
nextPut: aMsg [
<category: 'output'>
conManager sendMsg: aMsg.
]
]
SCCPConnectionBase subclass: SCCPConnection [
data: aDT [
"nothing implemented"
]
terminate [
"noting implemented"
]
]
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
]
]
Osmo.SCCPMessage extend [
sccpInitialDispatch: aHandler [
^ aHandler dispatchMessage: self.
]
sccpHandlerDispatchOn: aCon [
"Message is not handled here"
self logError: 'Unhandled SCCP packet %1' % {self class} area: #sccp.
^ false
]
]
Osmo.SCCPUDT extend [
sccpInitialDispatch: aHandler [
aHandler handleUDT: self.
^ true
]
]
Osmo.SCCPConnectionRequest extend [
sccpInitialDispatch: aHandler [
self logNotice: 'New incoming connection' area: #sccp.
aHandler confirmConnection: self.
^ true
]
]
Osmo.SCCPConnectionConfirm extend [
sccpHandlerDispatchOn: aCon [
aCon confirm: self.
^ true
]
]
Osmo.SCCPConnectionData extend [
sccpHandlerDispatchOn: aCon [
aCon data: self.
^ true
]
]
Osmo.SCCPConnectionReleased extend [
sccpHandlerDispatchOn: aCon [
aCon released: self.
aCon conManager removeConnection: aCon.
^ true
]
]
Osmo.SCCPConnectionReleaseComplete extend [
sccpHandlerDispatchOn: aCon [
aCon releaseComplete: self.
aCon conManager removeConnection: aCon.
^ true
]
]
Object subclass: SCCPHandler [
| connections last_ref connection sem |
<comment: 'I handle SCCP messages and have a complicated locking
dependency. It appears to be easier (but less efficient) to first hold
the SCCPhandler lock and then the lock of the connection. With this deps
deadlocks should not occur.'>
SCCPHandler class >> dissectMSG: aMsg [
^ MSGParser parse: (aMsg asByteArray).
]
2010-11-14 21:43:29 +00:00
SCCPHandler class >> new [
<category: 'creation'>
^ super new initialize; yourself
]
initialize [
<category: 'creation'>
sem := Semaphore forMutualExclusion.
]
2010-11-14 21:43:29 +00:00
registerOn: aDispatcher [
<category: 'creation'>
2010-11-14 21:43:29 +00:00
aDispatcher addHandler: Osmo.IPAConstants protocolSCCP
on: self with: #handleMsg:.
2010-11-14 21:43:29 +00:00
]
connection: aConnection [
<category: 'creation'>
connection := aConnection.
]
critical: aBlock [
<category: 'locking'>
^ sem critical: aBlock
]
addConnection: aConnection [
<category: 'public'>
sem critical: [
self connections add: aConnection.
aConnection srcRef: self assignSrcRef.
].
]
2010-11-28 09:14:15 +00:00
dispatchMessage: aMessage [
<category: 'public'>
sem critical: [
self connections do: [:each |
each srcRef = aMessage dst
ifTrue: [
^ aMessage sccpHandlerDispatchOn: each.
].
]
].
self logError: 'No one handled connection %1' % {aMessage dst} area: #sccp.
2010-11-28 09:14:15 +00:00
]
linkSetFailed [
"The underlying has failed, invalidate all connections"
<category: 'public'>
sem critical: [
self connections do: [:each |
self doTerminate: each].
connections := nil.
]
]
newConnection: aCon [
<category: 'protected'>
"Interesting for subclasses"
]
connectionSpecies [
<category: 'protected'>
"Interesting for subclasses"
^ SCCPConnection
]
handleUDT: aSCCP [
<category: 'protected'>
self logNotice: 'Incomind UDT message' area: #sccp.
]
removeConnection: aConnection [
<category: 'private'>
self connections remove: aConnection.
]
connectionTimeout: aConnection [
<category: 'private'>
self logError: 'SCCP Connection %1 timedout' % {aConnection srcRef} area: #sccp.
self removeConnection: aConnection.
]
confirmConnection: aMsg [
| con res |
<category: 'private'>
con := self connectionSpecies on: self.
"Confirm the message now and send any data"
con confirm: aMsg.
aMsg data ifNotNil: [
con data: aMsg.
].
"Confirm it without sending any new data bad"
res := Osmo.SCCPConnectionConfirm initWithSrc: (con srcRef) dst: (con dstRef).
self sendMsg: res toMessage.
self newConnection: con.
^ con.
]
handleMsg: aMsg [
| sccp |
<category: 'private'>
"I am called from the dispatcher for SCCP"
[
sccp := self class dissectMSG: aMsg.
] on: Exception do: [:e |
e logException: 'Failed to parse message' area: #sccp.
aMsg toMessageOrByteArray printNl.
2010-11-28 09:14:15 +00:00
^ false
].
sccp sccpInitialDispatch: self.
2010-11-14 21:43:29 +00:00
]
sendMsg: aMsg [
<category: 'private'>
"Send a SCCP message."
connection send: aMsg with: Osmo.IPAConstants protocolSCCP.
]
referenceIsFree: aRef [
<category: 'private'>
self connections do: [:each |
each srcRef = aRef
ifTrue: [
^ false
].
].
^ true
]
assignSrcRef [
<category: 'private'>
"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 [
<category: 'private'>
^ connections ifNil: [ connections := OrderedCollection new. ]
]
doTerminate: aCon [
<category: 'termination'>
"I kill the SCCP Connection."
[
aCon terminate
] on: Error do: [:each |
each logException: 'Failed to terminate %1' % {aCon srcRef} area: #sccp.
]
]
2010-11-14 21:43:29 +00:00
]