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

sccp: Dispatch via the polymorphism of smalltalk

This commit is contained in:
Holger Hans Peter Freyther 2011-06-15 16:44:22 +02:00
parent c122f64835
commit 20b808d3f0
1 changed files with 47 additions and 28 deletions

View File

@ -1,5 +1,5 @@
"
(C) 2010 by Holger Hans Peter Freyther
(C) 2010-2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -38,6 +38,11 @@ Object subclass: SCCPConnection [
queue := SharedQueue new.
]
conManager [
<category: 'accessing'>
^ conManager
]
conManager: aHandler [
<category: 'private'>
conManager := aHandler.
@ -204,6 +209,45 @@ Object subclass: MSGParser [
]
Osmo.SCCPMessage extend [
sccpHandlerDispatchOn: aCon [
"Message is not handled here"
self logError: 'Unhandled SCCP packet %1' % {self class} area: #sccp.
^ false
]
]
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'>
@ -240,34 +284,9 @@ Object subclass: SCCPHandler [
]
]
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 removeConnection: aConnection.
^ true
].
(aMessage isKindOf: Osmo.SCCPConnectionReleaseComplete)
ifTrue: [
aConnection releaseComplete: aMessage.
self removeConnection: aConnection.
^ true.
].
forwardMessage: aMessage with: aConnection [
^ aMessage sccpHandlerDispatchOn: aConnection.
self logError: 'Unhandled SCCP packet %1' % {aMessage class} area: #sccp.
"Message is not handled here"
^ false
]
dispatchMessage: aMessage [