aboutsummaryrefslogtreecommitdiffstats
path: root/SCCPHandler.st
diff options
context:
space:
mode:
Diffstat (limited to 'SCCPHandler.st')
-rw-r--r--SCCPHandler.st162
1 files changed, 147 insertions, 15 deletions
diff --git a/SCCPHandler.st b/SCCPHandler.st
index 6f57f63..4bba152 100644
--- a/SCCPHandler.st
+++ b/SCCPHandler.st
@@ -16,24 +16,26 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
-PackageLoader fileInPackage: 'OsmoNetwork'.
+PackageLoader
+ fileInPackage: 'OsmoCore';
+ fileInPackage: 'OsmoNetwork'.
-Object subclass: SCCPConnectionBase [
+Object subclass: SCCPConnectionState [
| 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 ]
+ SCCPConnectionState class >> stateInitial [ <category: 'state'> ^ 0 ]
+ SCCPConnectionState class >> stateRequested [ <category: 'state'> ^ 1 ]
+ SCCPConnectionState class >> stateConnected [ <category: 'state'> ^ 2 ]
+ SCCPConnectionState class >> stateReleased [ <category: 'state'> ^ 3 ]
+ SCCPConnectionState class >> stateReleaseComplete [ <category: 'state'> ^ 4 ]
+ SCCPConnectionState class >> stateTimeout [ <category: 'state'> ^ 5 ]
- SCCPConnectionBase class >> new [
+ SCCPConnectionState class >> new [
<category: 'creation'>
^ self shouldNotImplement
]
- SCCPConnectionBase class >> on: aHandler [
+ SCCPConnectionState class >> on: aHandler [
<category: 'creation'>
^ super new
initialize;
@@ -92,7 +94,7 @@ Object subclass: SCCPConnectionBase [
changeState: newState do: aBlock [
sem critical: [
state := newState.
- aBlock value
+ aBlock value.
]
]
@@ -102,6 +104,7 @@ Object subclass: SCCPConnectionBase [
"Send the confirmation now"
self changeState: self class stateRequested do: [
+ self startConnEstTimer.
res := Osmo.SCCPConnectionRequest
initWith: (self srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self nextPut: res toMessage.
@@ -113,6 +116,7 @@ Object subclass: SCCPConnectionBase [
self changeState: self class stateConnected do: [
self dstRef: aCC src.
+ self startConfirmTimer.
confirmSem signal.
]
]
@@ -122,6 +126,7 @@ Object subclass: SCCPConnectionBase [
<category: 'handling'>
self changeState: self class stateReleased do: [
+ self startReleaseTimer.
rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0.
self nextPut: rlsd toMessage.
]
@@ -132,7 +137,7 @@ Object subclass: SCCPConnectionBase [
"TODO: verify that we are in the right state"
self changeState: self class stateReleaseComplete do: [
- self terminate.
+ self finish.
]
]
@@ -145,7 +150,7 @@ Object subclass: SCCPConnectionBase [
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
- self terminate.
+ self finish.
]
]
@@ -162,6 +167,126 @@ Object subclass: SCCPConnectionBase [
]
]
+SCCPConnectionState subclass: SCCPConnectionBase [
+ | t_conn_est t_ias t_iar t_rel t_repeat_rel t_int |
+ <category: 'OSMO-SCCP'>
+ <comment: 'I add timeout handling based on the SCCP Connection State.
+My timeout values can be seen in ITU Q.714 Annex C.4'>
+
+ SCCPConnectionBase class [
+ tconnEstTime [ <category: 'timeouts'> ^ 60 ]
+ tiasTime [ <category: 'timeouts'> ^ 5 * 60 ]
+ tiarTime [ <category: 'timeouts'> ^ 15 * 60 ]
+ trelTime [ <category: 'timeouts'> ^ 15 ]
+ trepeatRelTime [ <category: 'timeouts'> ^ 15 ]
+ tintTime [ <category: 'timeouts'> ^ 60 ]
+ ]
+
+ stopAllTimers [
+ <category: 'private'>
+
+ sem critical: [
+ t_conn_est ifNotNil: [t_conn_est cancel].
+ t_ias ifNotNil: [t_ias cancel].
+ t_iar ifNotNil: [t_iar cancel].
+ t_rel ifNotNil: [t_rel cancel].
+ t_repeat_rel ifNotNil: [t_repeat_rel cancel]
+ ]
+ ]
+
+ finish [
+ <category: 'wrap up'>
+
+ self
+ stopAllTimers;
+ terminate.
+ ]
+
+ schedule: aTime block: aBlock [
+ "I make sure that the SCCPConnManager and SCCPCon locks are held"
+ <category: 'private'>
+
+ ^ Osmo.TimerScheduler instance
+ scheduleInSeconds: aTime block: [
+ conManager critical: [sem critical: [aBlock value]]].
+ ]
+
+ startConnEstTimer [
+ <category: 'conn-establishment'>
+ self stopAllTimers.
+ t_conn_est := self schedule: self class tconnEstTime block: [self conTimeout].
+ ]
+
+ conTimeout [
+ <category: 'conn-establishment'>
+ conManager connectionTimeout: self.
+ ]
+
+ startConfirmTimer [
+ <category: 'confirm-timer'>
+ t_conn_est ifNotNil: [t_conn_est cancel. t_conn_est := nil].
+
+ self startTias.
+ self startTiar.
+ ]
+
+ startTias [
+ <category: 'confirm-timer'>
+ t_ias ifNotNil: [t_ias cancel. t_ias := nil].
+ t_ias := self schedule: self class tiasTime block: [self sendInactivty].
+ ]
+
+ startTiar [
+ <category: 'confirm-timer'>
+ t_iar := self schedule: self class tiarTime block: [self sendRelease].
+ ]
+
+ sendInactivty [
+ <category: 'confirm-timer'>
+ self logError: 'IT sending is not implemented.' area: #sccp.
+ ]
+
+ sendRelease [
+ <category: 'confirm-timer'>
+ self logError: 'Releasing connection due inactivity.' area: #sccp.
+ self release.
+ ]
+
+ startReleaseTimer [
+ "We might be called multiple times and we use some variables to
+ figure out if we are the one or the other."
+ <category: 'release-timer'>
+
+ t_ias ifNotNil: [t_ias cancel].
+ t_iar ifNotNil: [t_iar cancel].
+
+ t_rel isNil
+ ifTrue: [
+ t_rel := self schedule: self class trelTime block: [self releaseTimeout]]
+ ifFalse: [
+ self startReleaseRepeatTimer.].
+ ]
+
+ releaseTimeout [
+ <category: 'release-timer'>
+ self logError: 'Release timeout.' area: #sccp.
+ t_int := self schedule: self class tintTime block: [self forceRelease].
+ self release.
+ ]
+
+ startReleaseRepeatTimer [
+ <category: 'release-timer'>
+ t_repeat_rel ifNotNil: [t_repeat_rel cancel. t_repeat_rel := nil].
+ t_repeat_rel := self schedule: self class trepeatRelTime block: [self release].
+ ]
+
+ forceRelease [
+ <category: 'release-timer'>
+ conManager addToFreezeList: self.
+ conManager connectionTimeout: self.
+ ]
+]
+
SCCPConnectionBase subclass: SCCPConnection [
data: aDT [
"nothing implemented"
@@ -364,9 +489,16 @@ deadlocks should not occur.'>
self connections remove: aConnection.
]
+ addToFreezeList: aConnection [
+ <category: 'private'>
+ "TODO: Implement the freeze list so some SCCP SRCREF will not be
+ assigned for a given time."
+ ]
+
connectionTimeout: aConnection [
<category: 'private'>
self logError: 'SCCP Connection %1 timedout' % {aConnection srcRef} area: #sccp.
+ self doTerminate: aConnection.
self removeConnection: aConnection.
]
@@ -451,9 +583,9 @@ deadlocks should not occur.'>
"I kill the SCCP Connection."
[
- aCon terminate
+ aCon finish.
] on: Error do: [:each |
- each logException: 'Failed to terminate %1' % {aCon srcRef} area: #sccp.
+ each logException: 'Failed to finish %1' % {aCon srcRef} area: #sccp.
]
]
]