1
0
Fork 0

oml: Move the init into a new class/method.

The goal is to a list of statements for the entire init instead
of just being state driven. I will also experiment with continuations
and then take this experience to the call control code of the MSC.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-03 19:55:28 +02:00
parent 36933f5734
commit 601ec9c9fa
5 changed files with 110 additions and 10 deletions

View File

@ -4,5 +4,6 @@ Eval [
fileIn: 'BTSConnection.st';
fileIn: 'TLV.st';
fileIn: 'OMLMsg.st';
fileIn: 'OML.st'.
fileIn: 'OML.st';
fileIn: 'OMLInit.st'.
]

View File

@ -20,7 +20,7 @@
simulating failure condition..."
Object subclass: BTS [
| site_mgr oml rsl |
| site_mgr oml rsl oml_queue oml_init |
<category: 'BTS-Core'>
<comment: 'A fake BTS to test the state machine and inject
RSL messages to test a network without RF.'>
@ -32,15 +32,21 @@ Object subclass: BTS [
rsl := nil.
oml := BTSOmlConnection new
onData: [:each | self handleOml: each];
onStop: [self stoppedOml];
onStop: [self omlStopped];
onConnect: [self omlConnected];
yourself.
"Make sure oml is fully assigned"
oml_queue := SharedQueue new.
oml connect: anAddress
]
stoppedOml [
siteManager [
<category: 'control'>
^ site_mgr
]
omlStopped [
<category: 'control'>
Transcript nextPutAll: 'OML Connection gone.'; nl.
]
@ -49,10 +55,11 @@ Object subclass: BTS [
<category: 'control'>
Transcript nextPutAll: 'OML Connected'; nl.
site_mgr := SiteManagerOML new
onData: [:each | self sendOML: each];
start;
yourself.
site_mgr := SiteManagerOML new.
"Start the OML init now in a new thread"
oml_init := OMLBTSInit initWith: self.
[[oml_init run ] ensure: [Transcript nextPutAll: 'OML-Init exited'; nl]] fork.
]
stop [
@ -61,6 +68,7 @@ Object subclass: BTS [
rsl isNil ifFalse: [rsl stop. rsl := nil].
oml isNil ifFalse: [oml stop. oml := nil].
oml_init isNil ifFalse: [oml_queue nextPut: nil. oml_init := nil].
]
sendOML: aMsg [
@ -68,9 +76,26 @@ Object subclass: BTS [
oml send: aMsg.
]
waitForOMLMsg [
<category: 'oml'>
"TODO: do something funny with continuations"
^ oml_queue next
]
handleOml: aMsg [
| oml |
<category: 'oml'>
Transcript nextPutAll: 'Got OML'; nl.
aMsg asByteArray printNl.
[
oml := OMLMessageBase parse: aMsg asByteArray readStream.
oml_queue nextPut: oml.
] on: Exception do: [:e |
Transcript nextPutAll: 'OML Parsing failed with'; nl.
e inspect.
Transcript
nextPutAll: 'With data: ';
nextPutAll: aMsg asByteArray printString;
nl.
]
]
]

View File

@ -111,7 +111,7 @@ Object subclass: OMLManagerBase [
]
OMLManagerBase subclass: SiteManagerOML [
| bts onData swActivated |
| bts onData swActivated swLoaded |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 SiteManager'>
@ -175,6 +175,7 @@ OMLManagerBase subclass: SiteManagerOML [
| fom |
<category: 'oml'>
swLoaded := false.
swActivated := false.
self basicStart.
self bts start.
@ -198,6 +199,11 @@ OMLManagerBase subclass: SiteManagerOML [
self forwardData: fom toMessage.
]
loadSoftware: aSWConfiguration [
<category: 'load'>
swLoaded := true.
]
siteManager [
<category: 'accessing'>
^ self

63
fakebts/OMLInit.st Normal file
View File

@ -0,0 +1,63 @@
"
(C) 2012 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/>.
"
"Attempt to have the OMLinit as a imperative routine"
Object subclass: OMLBTSInit [
| sm bts |
<category: 'OML-BTS'>
<comment: 'I try to simulate the start-up of a BTS. I am an
attempt to use continuations for writing an imperative init
script. This can be used to tweak it for various failure events'>
OMLBTSInit class >> initWith: aBts [
<category: 'creation'>
^ self new
bts: aBts;
yourself
]
bts: aBts [
<category: 'creation'>
bts := aBts.
sm := aBts siteManager
onData: [:each | self forwardOML: each];
yourself.
]
forwardOML: aMsg [
"It could be filtered here"
bts sendOML: aMsg
]
run [
| msg |
"1. Initialize the SM"
sm start.
"2. Activate the software"
msg := bts waitForOMLMsg.
msg class = FOMMessage
ifFalse: [self error: 'Failed to get a Formatted O&M message'].
msg omDataField class = OMLSWActivateRequestAck
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
Transcript nextPutAll: 'We were asked to activate something'; nl.
(Delay forSeconds: 1) wait.
sm loadSoftware: msg omDataField swConfiguration.
]
]

View File

@ -801,6 +801,11 @@ OMLDataField subclass: OMLSWActivateRequest [
<category: 'creation'>
sw_config := aSWConfig
]
swConfiguration [
<category: 'accessing'>
^ sw_config
]
]
OMLSWActivateRequest subclass: OMLSWActivateRequestAck [