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-openbsc-test/fakebts/OML.st

1028 lines
28 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/>.
"
Object subclass: OMLProcedure [
| procName |
<category: 'BTS-OML'>
<comment: 'I represent a OML Procedure by name'>
OMLProcedure class >> name: aName [
<category: 'creation'>
^ self new
procedureName: aName;
yourself
]
procedureName: aName [
<category: 'creation'>
procName := aName
]
procedureName [
^ procName
]
]
Object subclass: OMLManagerBase [
| attributes parent swActivated swLoaded |
<category: 'BTS-OML'>
<comment: 'I am a base class for GSM 12.21'>
OMLManagerBase class >> new [
<category: 'creation'>
^ super basicNew
basicInitialize;
initialize;
yourself
]
basicInitialize [
<category: 'creation'>
]
parent: aFather [
<category: 'internal'>
parent := aFather
]
siteManager [
<category: 'access'>
^ parent siteManager
]
sendStateChanged [
| oml sm |
<category: 'oml'>
"Create the state changed event"
oml := self createStateChange.
"Find the sitemanager"
sm := self siteManager.
sm forwardData: oml toMessage.
]
operationalState [
<category: 'state'>
^ attributes at: 'Operational State' ifAbsent: [nil].
]
availabilityStatus [
<category: 'state'>
^ attributes at: 'Availability Status' ifAbsent: [nil].
]
administrativeState [
<category: 'state'>
^ attributes at: 'Administrative State' ifAbsent: [nil].
]
administrativeState: aState [
<category: 'state'>
attributes at: 'Administrative State' put: aState.
]
createStateChange [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLStateChangedEventReport new
objectClass: self class objectClass;
objectInstance: self fomInstance;
operationalState: self operationalState;
availabilityStatus: self availabilityStatus;
administrativeState: self administrativeState;
yourself);
yourself.
]
createSwActivatedReport [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLSWActivatedReport new
objectClass: self class objectClass;
objectInstance: self fomInstance;
yourself);
yourself
]
createSwActivateRequest [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLSWActivateRequest new
objectClass: self class objectClass;
objectInstance: self fomInstance;
hwConfiguration: #(1 2 3 4 5 6);
swConfiguration: (
OMLSWConfiguration new
add: (OMLSWDescription new
fileId: #(1 2 3);
fileVersion: #(3 4 5);
yourself);
yourself);
yourself);
yourself.
]
initializeAttributes [
<category: 'oml'>
attributes := Dictionary new.
self class omlAttributes do: [:each |
attributes at: each attributeName put: each default copy].
]
basicStart [
<category: 'oml'>
swLoaded := false.
swActivated := false.
self
initializeAttributes;
sendStateChanged.
]
basicOpstart [
<category: 'oml'>
self operationalState state: OMLOperationalState enabled.
self availabilityStatus state: nil.
^ true
]
opstart [
^ self basicOpstart
]
loadSoftware: aSWConfiguration [
<category: 'load'>
swLoaded := true.
]
softwareActivated [
| op_state av_state |
(swActivated or: [swLoaded])
ifFalse: [^self error: 'SW not ready'].
"Report the software being activated"
self siteManager forwardData: self createSwActivatedReport toMessage.
"Update the state"
op_state := self operationalState.
op_state state: OMLOperationalState disabled.
av_state := self availabilityStatus.
av_state state: self class defaultActivatedState.
self sendStateChanged.
]
activateSoftware: aSWDescription [
<category: 'load'>
swActivated := true.
]
changeAdminState: aState [
self administrativeState: aState.
^ true
]
fomKey [
<category: 'oml'>
^ Array
with: self fomInstance
with: self class objectClass.
]
]
OMLManagerBase subclass: SiteManagerOML [
| bts onData |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 SiteManager'>
SiteManagerOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassSiteManager
]
SiteManagerOML class >> defaultActivatedState [
^ OMLAvailabilityStatus offline.
]
SiteManagerOML class >> omlAttributes [
<category: 'gsm-12.21'>
"Kill the default as everything inherits OMLAttribute now"
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Site Inputs');
add: (OMLAttribute name: 'Site Outputs');
add: (OMLAttribute name: 'SW Configuration');
yourself.
]
SiteManagerOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Establish TEI');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set Site Outputs');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
bts := BTSOML new
parent: self;
yourself
]
bts [
<category: 'acccessing'>
^ bts
]
onData: aData [
<category: 'creation'>
onData := aData.
]
start [
| fom |
<category: 'oml'>
self basicStart.
self bts start.
"Ask for the software being activated"
fom := self createSwActivateRequest.
self forwardData: fom toMessage.
]
opstart [
<category: 'load'>
(swActivated not or: [swLoaded not])
ifTrue: [^false].
self basicOpstart.
^ true
]
siteManager [
<category: 'accessing'>
^ self
]
forwardData: aMsg [
<category: 'private'>
onData value: aMsg
]
fomInstance [
<category: 'oml'>
^ FOMObjectInstance new
bts: 16rFF trx: 16rFF ts: 16rFF;
yourself
]
findObject: fomKey [
fomKey = self fomKey
ifTrue: [^self].
^ bts findObject: fomKey
]
]
OMLManagerBase subclass: BTSOML [
| radio_carrier baseband attributes |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 BTS'>
BTSOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassBTS
]
BTSOML class >> defaultActivatedState [
^ OMLAvailabilityStatus dependency.
]
BTSOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'BCCH ARFCN');
add: (OMLAttribute name: 'BSIC');
add: (OMLAttribute name: 'BTS Air Timer');
add: (OMLAttribute name: 'CCCH Load Ind. Period');
add: (OMLAttribute name: 'CCCH Load Threshold');
add: (OMLAttribute name: 'Connection Failure Criterion');
add: (OMLAttribute name: 'GSM Time');
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Intave Parameter');
add: (OMLAttribute name: 'Interterference Level Boundaries');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Max Timing Advance');
add: (OMLAttribute name: 'Ny1');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Overload Period');
add: (OMLAttribute name: 'RACH Busy Threshold');
add: (OMLAttribute name: 'RACH Load Averaging Slots');
add: (OMLAttribute name: 'SW Configuration');
add: (OMLAttribute name: 'T200');
yourself.
]
BTSOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Report Procedures');
add: (OMLProcedure name: 'Set BTS Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
radio_carrier := RadioCarrierOML new
parent: self;
id: 1;
yourself.
baseband := BasebandTransceiverOML new
parent: self;
id: 1;
yourself.
]
availableTrx [
<category: 'accessing'>
^ 1
]
radioCarrier: aNr [
<category: 'accessing'>
aNr = 1 ifFalse: [^self error: 'Wrong RadioCarrier number: ', aNr printString].
^ self radioCarrier
]
basebandTransceiver: aNr [
<category: 'accessing'>
aNr = 1 ifFalse: [^self error: 'Wrong Baseband number: ', aNr printString].
^ self basebandTransceiver
]
radioCarrier [
<category: 'accessing'>
^ radio_carrier
]
basebandTransceiver [
<category: 'accessing'>
^ baseband
]
start [
attributes := nil.
self basicStart.
self basebandTransceiver start.
self radioCarrier start.
]
btsAttributes: btsAttributes [
<category: 'oml'>
"FIXME: This should be copied into the attributes by GSM 12.21 name"
attributes := btsAttributes.
^ true
]
fomInstance [
<category: 'oml'>
^ parent fomInstance
bts: 16r0;
yourself.
]
findObject: fomKey [
self fomKey = fomKey
ifTrue: [^self].
fomKey second = radio_carrier class objectClass
ifTrue: [^radio_carrier findObject: fomKey].
^baseband findObject: fomKey.
]
bcchArfcn [
<category: 'accessing'>
^ attributes bcchArfcn.
]
]
OMLManagerBase subclass: RadioCarrierOML [
| id rcAttributes |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Radio carrier'>
RadioCarrierOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassRadioCarrier
]
RadioCarrierOML class >> defaultActivatedState [
^ OMLAvailabilityStatus offline.
]
RadioCarrierOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute name: 'ARFCN List');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Power Class');
add: (OMLAttribute name: 'RF Max Power Reduction');
add: (OMLAttribute name: 'SW Configuration');
yourself
]
RadioCarrierOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set RadioCarrier Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself
]
initialize [
<category: 'creation'>
]
start [
<category: 'oml'>
self basicStart.
]
id: anId [
<category: 'creation'>
id := anId
]
fomInstance [
^ parent fomInstance
trx: id - 1;
ts: 16rFF;
yourself.
]
radioCarrierAttributes: attributes [
<category: 'oml'>
"TODO: Merge into the attributes"
rcAttributes := attributes.
^ true
]
arfcnList [
"TODO: check for the arfcn list inside the attributes"
^ rcAttributes arfcnList
]
findObject: fomKey [
self fomKey = fomKey
ifTrue: [^self].
self error: 'Unknown object'.
]
]
OMLManagerBase subclass: BasebandTransceiverOML [
| channels onData id mainBts |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Baseband Transceiver'>
BasebandTransceiverOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassBasebandTransceiver
]
BasebandTransceiverOML class >> defaultActivatedState [
^ OMLAvailabilityStatus dependency
]
BasebandTransceiverOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'SW Configuration');
yourself
]
BasebandTransceiverOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Connect Terrestrial Signalling');
add: (OMLProcedure name: 'Disconnect Terrestrial Signalling');
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
channels := Array new: 8.
(1 to: 8) do: [:each |
channels at: each put: (ChannelOML new
channel: each;
parent: self; yourself).
].
]
channel: aChannel [
<category: 'accessing'>
^ channels at: aChannel.
]
start [
<category: 'oml'>
self basicStart.
channels do: [:each | each start]
]
id: anId [
<category: 'creation'>
id := anId
]
fomInstance [
<category: 'oml'>
^ parent fomInstance
trx: id - 1;
yourself.
]
findObject: fomKey [
fomKey = self fomKey
ifTrue: [^self].
fomKey second = ChannelOML objectClass
ifFalse: [^self error: 'Unknown objectClass'].
channels do: [:each | | res |
res := each findObject: fomKey.
res isNil ifFalse: [^res]].
^ self error: 'Unknown radio channel object'.
]
onData: aCb [
<category: 'sending'>
onData := aCb.
]
forwardRsl: aMsg [
<category: 'sending'>
onData value: aMsg.
]
mainBts: aBTS [
<category: 'creation'>
mainBts := aBTS
]
mainBts [
<category: 'access'>
^ mainBts
]
]
OMLChannelCombination extend [
performOnChannel: aChannel [
| ch sel |
<category: '*-BTS-OML-ChannelOML'>
ch := (self class channelNames at: comb) asString.
ch at: 1 put: (ch at: 1) asUppercase.
sel := 'create', ch.
aChannel perform: sel asSymbol.
]
]
Object subclass: LogicalChannel [
| number free sapis ts onDataCb onReleaseReqCB conn_id |
<category: 'BTS-OML'>
<comment: 'I am a logical that is on the ChannelOML.'>
LogicalChannel class >> initWith: aNumber [
<category: 'creation'>
^ self new
initialize;
number: aNumber;
yourself
]
initialize [
<category: 'creation'>
free := true.
sapis := Dictionary new.
]
ts [
<category: 'accessing'>
^ ts
]
ts: aTs [
<category: 'creation'>
ts := aTs
]
number: aNumber [
<category: 'creation'>
number := aNumber
]
isFree [
<category: 'query'>
^ free
]
allocate [
<category: 'channel-allocation'>
self isFree ifFalse: [^false].
free := false.
^ true.
]
release [
<category: 'channel-allocation'>
self isFree ifTrue: [^false].
free := true.
^ true
]
sapiIsEstabliashed: aSapi [
<category: 'sapi'>
^ sapis includesKey: aSapi.
]
sendData: aMsg on: aSapi [
| rsl |
<category: 'sapi'>
(sapis includesKey: aSapi)
ifFalse: [^self error: 'SAPI is not established'].
rsl := RSLDataIndication new
channelNumber: self channelNumber;
linkIdentifier: {aSapi} asRSLAttributeData;
l3Information: aMsg asRSLAttributeData.
ts forwardRsl: rsl toMessage.
]
establish: aMsg on: aSapi [
| rsl |
<category: 'sapi'>
(sapis includesKey: aSapi)
ifTrue: [^self error: 'SAPI is already established.'].
"Remember which side allocated the SAPI."
sapis at: aSapi put: #ms.
"Create the Establish Indication with the message."
rsl := RSLEstablishIndication new
channelNumber: self channelNumber;
linkIdentifier: {aSapi} asRSLAttributeData;
l3Information: aMsg asRSLAttributeData.
ts forwardRsl: rsl toMessage.
]
channelNumber [
| nr mask chan_nr |
<category: 'chan'>
"Initialize"
mask := 0.
nr := ts channelCombination.
1 to: nr highBit - 1 do: [:each |
mask := mask bitAt: each put: 1].
chan_nr := nr bitOr: (number - 1 bitAnd: mask).
chan_nr := chan_nr bitShift: 3.
chan_nr := chan_nr bitOr: ts timeslotNumber - 1.
^ RSLChannelNumber new
data: (ByteArray with: chan_nr);
yourself.
]
releaseRequested [
<category: 'release'>
self isFree
ifTrue: [^self error: 'Lchan was not allocated.'].
"TODO: check if there is a release handler installed."
self defaultRelease.
]
defaultRelease [
| ack |
<category: 'release'>
conn_id ifNotNil: [
| ind |
ind := RSLIPADeleteConnectionInd new
defaultValues;
channelNumber: self channelNumber;
connectionIdentifier: conn_id;
yourself.
conn_id := nil.
ts forwardRsl: ind toMessage.
].
free := true.
ack := RSLRFChannelReleaseAck new
channelNumber: self channelNumber;
yourself.
ts forwardRsl: ack toMessage.
]
onDataRequest: aBlock [
<category: 'input'>
onDataCb := aBlock.
]
onReleaseReqCB: aBlock [
<category: 'input'>
onReleaseReqCB := aBlock
]
dataRequest: aMsg sapi: aSapi [
<category: 'input'>
onDataCb value: aMsg value: aSapi.
]
releaseSapiRequest: aSapi [
| rsl |
<category: 'input'>
"Remove the key and if no exception is generated, continue"
sapis removeKey: aSapi.
onReleaseReqCB isNil
ifFalse: [onReleaseReqCB value: aSapi].
rsl := RSLReleaseConfirm new
channelNumber: self channelNumber;
linkIdentifier: (ByteArray with: aSapi) asRSLAttributeData;
yourself.
ts forwardRsl: rsl toMessage.
]
releaseSapi: aSapi [
| rsl |
<category: 'release'>
"Remove the key and if no exception is generated, continue"
sapis removeKey: aSapi.
rsl := RSLReleaseIndication new
channelNumber: self channelNumber;
linkIdentifier: (ByteArray with: aSapi) asRSLAttributeData;
yourself.
ts forwardRsl: rsl toMessage.
]
ipaConnId [
<category: 'ipa-audio'>
^ conn_id
]
ipaConnId: anId [
<category: 'ipa-audio'>
conn_id := anId
]
]
OMLManagerBase subclass: ChannelOML [
| chan_nr channels config |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Channel'>
ChannelOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassChannel
]
ChannelOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute name: 'ARFCN List');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'Channel Conbination');
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'HSN');
add: (OMLAttribute name: 'MAIO');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'SW Configuration');
add: (OMLAttribute name: 'TSC');
yourself
]
ChannelOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Connect Terrestrial Signalling');
add: (OMLProcedure name: 'Disconnect Terrestrial Signalling');
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set Channel Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
]
start [
<category: 'oml'>
self basicStart.
]
channel: aNr [
<category: 'creation'>
chan_nr := aNr.
]
fomInstance [
^ parent fomInstance
ts: chan_nr - 1;
yourself
]
findObject: fomKey [
^ fomKey = self fomKey
ifTrue: [self]
ifFalse: [nil].
]
setChannelAttributes: chanAttr [
attributes at: 'Channel Combination' put: chanAttr channelCombination.
^ true
]
opstart [
super opstart.
(attributes at: 'Channel Combination') performOnChannel: self.
^ true
]
createChannel: aNr[
<category: 'opstart'>
channels at: aNr put:
((LogicalChannel initWith: aNr)
ts: self; yourself)
]
createChanBCCHComb [
<category: 'opstart'>
"In this model we only care about allocatable channels right now.
We don't schedule anything on the BCCH or such."
config := RSLChannelNumber cnSdcch4Acch.
channels := Array new: 4.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanSDCCH [
<category: 'opstart'>
config := RSLChannelNumber cnSdcch8Acch.
channels := Array new: 8.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanTCHH [
<category: 'opstart'>
config := RSLChannelNumber cnLmAcch.
channels := Array new: 2.
1 to: channels size do: [:each |
self createChannel: each]
]
createChanTCHF [
<category: 'opstart'>
config := RSLChannelNumber cnBmAcch.
channels := Array new: 1.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanPDCH [
<category: 'opstart'>
"TODO... PDCH config"
]
lchan: aNr [
<category: 'access'>
^ channels at: aNr
]
forwardRsl: aMsg [
<category: 'sending'>
"Forward it from the TS -> TRX"
^ parent forwardRsl: aMsg
]
channelCombination [
<category: 'configuration'>
^ config
]
timeslotNumber [
<category: 'configuration'>
^ chan_nr
]
]