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-network/m2ua/M2UALayerManagement.st

128 lines
3.3 KiB
Smalltalk

"
(C) 2013 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/>.
"
Object subclass: M2UALayerManagement [
| targetState managedProcess |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I am taking the LayerManagement control for an M2UAApplicationServiceProcess.
Currently you can tell me the ASP state this class should be in
and I will react to to the events from the ASP.'>
applicationServerProcess: aProcess [
<category: 'creation'>
managedProcess := aProcess.
managedProcess
onSctpEstablished: [self sctpEstablished];
onSctpRestarted: [self sctpEstablished];
onError: [:msg | self m2uaError: msg];
onNotify: [:type :ident | self m2uaNotify: type ident: ident];
onAspActive: [self m2uaActive];
onAspInactive: [self m2uaInactive];
onAspDown: [self m2uaDown];
onAspUp: [self m2uaUp]
]
manage [
"I begin to manage the process."
<category: 'creation'>
managedProcess
sctpRelease;
sctpEstablish
]
targetState: aState [
"Use the M2UAAspState subclasses for the states"
<category: 'creation'>
targetState := aState
]
applicationServerProcess [
<category: 'accessing'>
^managedProcess
]
m2uaActive [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateInactive
ifTrue: [managedProcess aspInactive]
ifFalse: [managedProcess aspDown]
]
m2uaDown [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
"There is only one way forward"
managedProcess aspUp
]
m2uaError: aMsg [
<category: 'as-process-callbacks'>
self logNotice: 'M2UA Error.' area: #m2ua
]
m2uaInactive [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateActive
ifTrue: [managedProcess aspActive]
ifFalse: [managedProcess aspDown]
]
m2uaNotify: type ident: ident [
"TODO: Check the type/ident"
<category: 'as-process-callbacks'>
]
m2uaUp [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateActive
ifTrue: [managedProcess aspActive]
ifFalse: [managedProcess aspInactive]
]
sctpEstablished [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self].
"There is only one way forward"
managedProcess aspUp
]
targetReached [
]
]