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

sccp: Reorder functions, document, explain what kind of locking is used

This commit is contained in:
Holger Hans Peter Freyther 2011-06-20 12:02:18 +02:00
parent eda5c4bd08
commit dbea609d06
2 changed files with 69 additions and 50 deletions

View File

@ -271,51 +271,58 @@ Osmo.SCCPConnectionReleaseComplete extend [
Object subclass: SCCPHandler [
| connections last_ref connection sem |
<comment: 'I handle SCCP messages'>
<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).
]
SCCPHandler class >> new [
<category: 'creation'>
^ super new initialize; yourself
]
initialize [
<category: 'creation'>
sem := Semaphore forMutualExclusion.
]
registerOn: aDispatcher [
<category: 'creation'>
aDispatcher addHandler: Osmo.IPAConstants protocolSCCP
on: self with: #handleMsg:.
]
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.
].
]
removeConnection: aConnection [
self connections remove: aConnection.
]
registerOn: aDispatcher [
aDispatcher addHandler: Osmo.IPAConstants protocolSCCP
on: self with: #handleMsg:.
]
connectionTimeout: aConnection [
self logError: 'SCCP Connection %1 timedout' % {aConnection srcRef} area: #sccp.
sem critical: [
self removeConnection: aConnection.
]
]
forwardMessage: aMessage with: aConnection [
^ aMessage sccpHandlerDispatchOn: aConnection.
]
dispatchMessage: aMessage [
<category: 'public'>
sem critical: [
self connections do: [:each |
each srcRef = aMessage dst
ifTrue: [
^ self forwardMessage: aMessage with: each.
^ aMessage sccpHandlerDispatchOn: each.
].
]
].
@ -323,20 +330,46 @@ Object subclass: SCCPHandler [
self logError: 'No one handled connection %1' % {aMessage dst} area: #sccp.
]
dissectMSG: aMsg [
^ MSGParser parse: (aMsg asByteArray).
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.
@ -356,9 +389,11 @@ Object subclass: SCCPHandler [
handleMsg: aMsg [
| sccp |
<category: 'private'>
"I am called from the dispatcher for SCCP"
[
sccp := self dissectMSG: aMsg asByteArray.
sccp := self class dissectMSG: aMsg.
] on: Exception do: [:e |
e logException: 'Failed to parse message' area: #sccp.
aMsg toMessageOrByteArray printNl.
@ -368,16 +403,8 @@ Object subclass: SCCPHandler [
sccp sccpInitialDispatch: self.
]
handleUDT: aSCCP [
self logNotice: 'Incomind UDT message' area: #sccp.
]
connection: aConnection [
connection := aConnection.
]
sendMsg: aMsg [
<category: 'private'>
"Send a SCCP message."
connection send: aMsg with: Osmo.IPAConstants protocolSCCP.
]
@ -395,6 +422,7 @@ Object subclass: SCCPHandler [
]
assignSrcRef [
<category: 'private'>
"Find a free SCCP reference"
1 to: 16rFFFFFE do: [:dummy |
| ref |
@ -409,6 +437,7 @@ Object subclass: SCCPHandler [
]
connections [
<category: 'private'>
^ connections ifNil: [ connections := OrderedCollection new. ]
]
@ -422,15 +451,5 @@ Object subclass: SCCPHandler [
each logException: 'Failed to terminate %1' % {aCon srcRef} area: #sccp.
]
]
linkSetFailed [
"The underlying has failed, invalidate all connections"
<category: 'failure'>
sem critical: [
self connections do: [:each |
self doTerminate: each].
connections := nil.
]
]
]

View File

@ -491,12 +491,12 @@ SCCPConnection subclass: SCCPMockConnection [
]
SCCPHandler subclass: SCCPHandlerNonRec [
connectionSpecies [
^ SCCPMockConnection
SCCPHandlerNonRec class >> dissectMSG: aMsg [
^ Osmo.SCCPMessage decode: aMsg asByteArray.
]
dissectMSG: aMsg [
^ Osmo.SCCPMessage decode: aMsg asByteArray.
connectionSpecies [
^ SCCPMockConnection
]
]