smalltalk
/
osmo-st-all
Archived
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-all/osmo-st-openbsc-test/fakebts/OMLInit.st

419 lines
13 KiB
Smalltalk

"
(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: OMLInstanceInit [
| queue omlTarget omlInit |
<category: 'BTS-OML-Tests'>
<comment: 'I am the helper class for powering up a single
instance. I am easily extendable for the different phases.'>
OMLInstanceInit class >> on: anOMLInstance withInit: omlInit withQueue: aQueue [
<category: 'creation'>
^ self new
omlTarget: anOMLInstance;
omlInit: omlInit;
queue: aQueue;
yourself
]
queue: aQueue [
<category: 'creation'>
queue := aQueue
]
omlTarget: aTarget [
<category: 'creation'>
omlTarget := aTarget
]
omlInit: anInit [
<category: 'creation'>
omlInit := anInit
]
waitForSWActivation [
| msg |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLSWActivateRequestAck
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
Transcript nextPutAll: 'SWActivation for '; nextPutAll: omlTarget class name; nl.
omlTarget loadSoftware: msg omDataField swConfiguration.
]
activateSoftware [
| msg ack |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLActivateSoftware
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
omlTarget activateSoftware: msg omDataField swDescription.
ack := msg createAck.
omlInit forwardOML: ack toMessage.
]
waitForAttributes [
<category: 'private'>
"Depending on the object all attributes should be set before the
opstart"
]
waitForOpStart [
| msg ack res |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLOpstart
ifFalse: [^self error: 'Failed to get the Opstart.'].
res := omlTarget opstart.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
"TODO: required by GSM12.21 but problematic with GSM 12.21"
"omlTarget sendStateChanged."
]
start: onActivatedBlock [
"1. Load the software"
self waitForSWActivation.
"2. Activate the software. The stateChanged triggered and activated
report are not the same as with the nanoBTS."
self activateSoftware.
"3. The SM is up launch the BTS"
omlTarget softwareActivated.
onActivatedBlock value.
"4. OpStart or activate requests.."
self waitForAttributes.
self waitForOpStart.
"The below exposes a bug in the OpenBSC OML init. The graphics on page
16 of 12.21 is pretty clear that we should send a chaged state event
report... but sending 'Enabled' again will trigger a new opstart."
"dest sendStateChanged. -- causes the BSC to send OpStart again"
Transcript nextPutAll: 'Opstarted ', omlTarget class name; nl.
]
]
OMLInstanceInit subclass: OMLBTSInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the BTS Instance and deal with attributes'>
waitForAttributes [
| msg res ack |
<category: 'protected'>
msg := queue next.
msg omDataField class = OMLSetBTSAttributes
ifFalse: [self error: 'Failed to get SetBTSAttributes'].
res := omlTarget btsAttributes: msg omDataField.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
]
]
OMLInstanceInit subclass: OMLTrxInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the TRX Instance and deal with attributes'>
]
OMLInstanceInit subclass: OMLRadioCarrierInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the TRX Instance and deal with attributes'>
waitForAttributes [
| msg res ack |
<category: 'radio-carrier'>
msg := queue next.
msg omDataField class = OMLSetRadioCarrierAttributes
ifFalse: [self error: 'Failed to get RadioCarrier Attributes'].
res := omlTarget radioCarrierAttributes: msg omDataField.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
]
]
Object subclass: OMLBTSInit [
| sm bts queues |
<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. The
execution starts in the the >>#run selector which will spawn the
SiteManager, the SiteManager will spawn the BTS, the BTS will spawn
the RadioCarrier and the BasebandTransceiver and finally the RadioChannels
will be spawned. Then it waits for all init processes to have
finished. The AdminLock is handled out-of-band. Another way to
write this code is to have a loop and a local state machine.'>
OMLBTSInit class >> initWith: aBts [
<category: 'creation'>
^ self new
bts: aBts;
yourself
]
bts: aBts [
<category: 'creation'>
bts := aBts.
sm := aBts siteManager.
]
forwardOML: aMsg [
"It could be filtered here"
bts sendOML: aMsg
]
checkIsFOM: msg [
<category: 'verify'>
msg class = FOMMessage
ifTrue: [^true].
msg class = IPAFOMMessage
ifTrue: [^true].
msg inspect.
^self error: 'Failed to get a (IPA) Formatted O&M message'
]
startRSL: aRsl on: aTrx [
| port |
port := (aRsl port data asByteArray ushortAt: 1) swap16.
bts startRSL: port streamId: aRsl streamId data first on: aTrx.
^ true
]
smInit: aSem [
| smQueue btsProc btsSem init |
"1. Initialize the SM"
smQueue := SharedQueue new.
queues := Dictionary new
at: sm fomKey put: smQueue;
yourself.
sm start.
init := OMLInstanceInit on: sm withInit: self withQueue: smQueue.
"Get the SM into the enabled state"
btsSem := Semaphore new.
init start: [
btsProc := [self btsInit: btsSem] fork.
btsProc name: 'BTS Init process'.
].
btsSem wait.
"Enable the SM now.. OpenBSC will send a Opstart again..."
sm availabilityStatus state: nil.
sm sendStateChanged.
aSem signal.
]
initBtsInstance: bts withQueue: btsQueue [
^ OMLBTSInstanceInit on: bts withInit: self withQueue: btsQueue.
]
btsInit: aSem [
| btsQueue bts init trxSem rcSem |
btsQueue := SharedQueue new.
bts := sm bts.
queues at: bts fomKey put: btsQueue.
"1. Activate the software"
self forwardOML: bts createSwActivateRequest toMessage.
init := self initBtsInstance: bts withQueue: btsQueue.
"Get the SM into the enabled state"
trxSem := Semaphore new.
rcSem := Semaphore new.
init start: [
"Start all trx and radio carriers"
1 to: bts availableTrx do: [:each |
| trxProc rcProc |
trxProc := [self trxInit: trxSem on: (bts basebandTransceiver: each)] fork.
trxProc name: 'TRX(%1) Init process' % {each}.
rcProc := [self rcInit: rcSem on: (bts radioCarrier: each)] fork.
rcProc name: 'Radio-Carrier(%1) Init process' % {each}.
].
].
"Now wait for all of them to initialize"
1 to: bts availableTrx do: [:each |
trxSem wait.
rcSem wait.
].
bts availabilityStatus state: nil.
bts sendStateChanged.
aSem signal.
]
trxInit: aSem on: trx [
| trxQueue init msg res ack tss |
trxQueue := SharedQueue new.
queues at: trx fomKey put: trxQueue.
"1. Activate the software"
self forwardOML: trx createSwActivateRequest toMessage.
init := OMLTrxInstanceInit on: trx withInit: self withQueue: trxQueue.
"Get the SM into the enabled state"
init start: [].
"Wait for the RSL Connect"
msg := trxQueue next.
msg omDataField class = IPAOMLRSLConnect
ifFalse: [self error: 'Failed to get the RSL Connect'].
res := self startRSL: msg omDataField on: trx.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
"TODO: there is no proper dependency handling"
"Start the RadioCarrier now"
tss := OrderedCollection new.
1 to: 8 do: [:each | | tsProc tsSem |
tsSem := Semaphore new.
tsProc := [self tsInit: (trx channel: each) with: tsSem] fork.
tsProc name: 'TS(%1) init' % {each}.
tss add: tsSem->tsProc.
].
"Wait for all TSs to be up"
tss do: [:each | each key wait].
trx availabilityStatus state: nil.
trx sendStateChanged.
aSem signal.
]
rcInit: aSem on: rc [
| rcQueue init |
rcQueue := SharedQueue new.
queues at: rc fomKey put: rcQueue.
"1. Activate the software"
self forwardOML: rc createSwActivateRequest toMessage.
init := OMLRadioCarrierInstanceInit on: rc withInit: self withQueue: rcQueue.
"Get the SM into the enabled state"
init start: [].
rc availabilityStatus state: nil.
rc sendStateChanged.
aSem signal.
]
tsInit: aTs with: tsSem [
| tsQueue msg res ack |
<category: 'init'>
tsQueue := SharedQueue new.
queues at: aTs fomKey put: tsQueue.
"1. Initialize the TS no need to activate the software"
aTs operationalState state: OMLOperationalState disabled.
"They are just offline but... OpenBSC has a bug/quirk for the nanoBTS"
aTs availabilityStatus state: OMLAvailabilityStatus dependency.
aTs sendStateChanged.
msg := tsQueue next.
msg omDataField class = OMLSetChannelAttributes
ifFalse: [^self error: 'Failed to get the SetChannelAttributes'].
res := aTs setChannelAttributes: msg omDataField.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
"Opstart it now"
msg := tsQueue next.
msg omDataField class = OMLOpstart
ifFalse: [^self error: 'Failed to get the Opstart.'].
res := aTs opstart.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
aTs availabilityStatus state: nil.
aTs sendStateChanged.
tsSem signal.
]
handleAdminChange: aMsg [
| target res key |
"Handle out of place admin changes"
key := Array
with: aMsg omDataField objectInstance
with: aMsg omDataField objectClass.
target := sm findObject: key.
res := target changeAdminState: aMsg omDataField adminState.
self forwardOML: (aMsg createResponse: res) toMessage.
]
forwardToQueue: aMsg [
| key |
<category: 'forward'>
key := Array
with: aMsg omDataField objectInstance
with: aMsg omDataField objectClass.
(queues at: key) nextPut: aMsg.
]
run [
| smProc sem |
"0. Initialize all queues"
sem := Semaphore new.
smProc := [self smInit: sem] fork.
smProc name: 'SiteManager init'.
"1. dispatch messages"
[
| msg |
msg := bts waitForOMLMsg.
msg isNil ifTrue: [
Transcript nextPutAll: 'OML End of connection'; nl.
^false].
self checkIsFOM: msg.
(msg omDataField class = OMLChangeAdminState)
ifTrue: [self handleAdminChange: msg]
ifFalse: [self forwardToQueue: msg].
sem wouldBlock not
ifTrue: [
"Be lazy and terminate.. on-going OML messages will not
be handled as of now."
Transcript nextPutAll: 'BTS is fully initialized.'; nl.
bts omlUp.
^true]
"Errors should cause an exception and termination"
] repeat.
]
]