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/OMLMsg.st

1611 lines
40 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/>.
"
PackageLoader fileInPackage: #OsmoNetwork.
Iterable extend [
asOMLAttributeData [
<category: '*-BTS-OML-Msg'>
^ OMLAttributeData new
data: self; yourself
]
]
Object subclass: FOMObjectInstance [
| bts trx ts |
<category: 'BTS-OML-Msg'>
<comment: 'I represent the Object Instance of a Formatted O&M message'>
FOMObjectInstance class >> readFrom: aStream [
| bts trx ts |
<category: 'instance'>
^ FOMObjectInstance new
bts: aStream next;
trx: aStream next;
ts: aStream next;
yourself
]
bts: aBTS [
<category: 'creation'>
bts := aBTS
]
trx: aTRX [
<category: 'creation'>
trx := aTRX
]
ts: aTS [
<category: 'creation'>
ts := aTS
]
bts: aBTS trx: aTRX ts: aTS [
<category: 'creation'>
bts := aBTS.
trx := aTRX.
ts := aTS.
]
bts [
<category: 'accessing'>
^ bts
]
trx [
<category: 'accessing'>
^ trx
]
ts [
<category: 'accessing'>
^ ts
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putByte: bts;
putByte: trx;
putByte: ts.
]
= anInstance [
<category: 'testing'>
bts = anInstance bts
ifFalse: [^false].
trx = anInstance trx
ifFalse: [^false].
ts = anInstance ts
ifFalse: [^false].
^ true
]
hash [
<category: 'testing'>
^ ((bts bitShift: 16) + (trx bitShift: 8) + ts) hash
]
]
Object subclass: OMLAttribute [
| attrName default |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 Attribute and Parameters'>
OMLAttribute class [
name: aName [
<category: 'creation'>
^ self new
attributeName: aName;
yourself
]
name: aName default: aDefault [
<category: 'creation'>
^ self new
attributeName: aName;
default: aDefault;
yourself
]
attrOperationalState [
<category: 'attributes'>
^ 16r24
]
attrAvailabilityStatus [
<category: 'attributes'>
^ 16r07
]
attrAdministrativeState [
<category: 'attributes'>
^ 16r04
]
attrSWConfiguration [
<category: 'attributes'>
^ 16r41
]
attrSWDescription [
<category: 'attributes'>
^ 16r42
]
attrHWConfiguration [
<category: 'attributes'>
^ 16r16
]
attrFileId [
<category: 'attributes'>
^ 16r12
]
attrFileVersion [
<category: 'attributes'>
^ 16r13
]
attrInterferenceLevelBoundaries [
<category: 'attributes'>
^ 16r19
]
attrIntave [
<category: 'attributes'>
^ 16r18
]
attrConnectionFailureCriterion [
<category: 'attributes'>
^ 16r0E
]
attrT200 [
<category: 'attributes'>
^ 16r33
]
attrMaxTimingAdvance [
<category: 'attributes'>
^ 16r1F
]
attrOverloadPeriod [
<category: 'attributes'>
^ 16r25
]
attrCCCHLoadThreshold [
<category: 'attributes'>
^ 16r0C
]
attrCCCHLoadIndicationPeriod [
<category: 'attributes'>
^ 16r0B
]
attrRACHBusyThreshold [
<category: 'attributes'>
^ 16r2A
]
attrRACHLoadAveragingSlots [
<category: 'attributes'>
^ 16r2B
]
attrBTSAirTimer [
<category: 'attributes'>
^ 16r0A
]
attrNy1 [
<category: 'attributes'>
^ 16r23
]
attrBCCHArfcn [
<category: 'attributes'>
^ 16r08
]
attrBSIC [
<category: 'attributes'>
^ 16r09
]
attrStartingTime [
<category: 'attributes'>
^ 16r32
]
attrMaxPowerReduction [
<category: 'attributes'>
^ 16r2D
]
attrARFCNList [
<category: 'attributes'>
^ 16r05
]
attrChannelCombination [
<category: 'attributes'>
^ 16r0D
]
attrHSN [
<category: 'attributes'>
^ 16r15
]
attrMAIO [
<category: 'attributes'>
^ 16r1B
]
attrTSC [
<category: 'attributes'>
^ 16r40
]
attrRequiredAttributes [
<category: 'attributes'>
^ 16r1A
]
asTLVDescription [
<category: 'parsing'>
^ Osmo.TLVDescription new
parseClass: self;
tag: self attributeType;
yourself
]
parseLength: aStream [
<category: 'parsing'>
^ ((aStream next: 2) asByteArray ushortAt: 1) swap16
]
readFrom: aStream with: anAttr [
<category: 'parsing'>
^ self readFrom: aStream
]
]
attributeName: aName [
<category: 'creation'>
attrName := aName
]
attributeName [
<category: 'accessing'>
^ attrName
]
default: aDefault [
<category: 'creation'>
default := aDefault
]
default [
<category: 'creation'>
^ default
]
writeWithTag: aMsg [
<category: 'serialize'>
"Writing the value with the default tag"
aMsg putByte: self class attributeType.
self writeOn: aMsg.
]
writeOn: aMsg with: attr [
^ self writeOn: aMsg.
]
]
OMLAttribute subclass: OMLOperationalState [
| state |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 Operational State'>
"TODO: This could be a list of states..."
OMLOperationalState class >> attributeType [
<category: 'parsing'>
^ self attrOperationalState
]
OMLOperationalState class [
disabledState [
<category: 'creation'>
^ self new
state: self disabled;
yourself.
]
disabled [
<category: 'attributes'>
^ 1
]
enabled [
<category: 'attributes'>
^ 2
]
null [
<category: 'attributes'>
^ 16rFF
]
]
state [
<category: 'accessing'>
^ state
]
state: aState [
<category: 'creation'>
state := aState.
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putByte: state.
]
]
OMLAttribute subclass: OMLAvailabilityStatus [
| state |
<category: 'BTS-OML'>
<comment: 'I represent the 9.4.7 Availability Status'>
OMLAvailabilityStatus class >> attributeType [
<category: 'parsing'>
^ self attrAvailabilityStatus
]
OMLAvailabilityStatus class [
notInstalledState [
<category: 'creation'>
^ self new
state: self notInstalled;
yourself.
]
inTest [
<category: 'attributes'>
^ 0
]
failed [
<category: 'attributes'>
^ 1
]
powerOff [
<category: 'attributes'>
^ 2
]
offline [
<category: 'attributes'>
^ 3
]
dependency [
<category: 'attributes'>
^ 5
]
degraded[
<category: 'attributes'>
^ 6
]
notInstalled [
<category: 'attributes'>
^ 7
]
]
state [
<category: 'accessing'>
^ state
]
state: aState [
<category: 'creation'>
state := aState.
]
writeOn: aMsg [
<category: 'serialize'>
state isNil
ifTrue: [
aMsg putLen16: 0]
ifFalse: [
aMsg
putLen16: 1;
putByte: state].
]
]
OMLAttribute subclass: OMLAdminState [
| state |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 Administrative State'>
OMLAdminState class >> attributeType [
<category: 'parsing'>
^ self attrAdministrativeState
]
OMLAdminState class >> readFrom: aStream [
<category: 'parsing'>
^ self new
state: aStream next;
yourself
]
OMLAdminState class [
lockedState [
<category: 'creation'>
^ self new
state: self locked;
yourself
]
locked [
<category: 'attributes'>
^ 16r01
]
unlocked [
<category: 'attributes'>
^ 16r02
]
shuttingDown [
<category: 'attributes'>
^ 16r03
]
notSupported [
<category: 'attributes'>
^ 16rFF
]
]
state: aState [
<category: 'creation'>
state := aState.
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putByte: state.
]
]
OMLAttribute subclass: OMLAttributeData [
| data |
<category: 'BTS-OML'>
<comment: 'I am a dummy holder for a plain byte array'>
OMLAttributeData class >> readFrom: aStream with: anAttr [
anAttr hasLength
ifTrue: [^self readFrom: aStream].
^ OMLAttributeData new
data: (aStream next: anAttr valueSize);
yourself
]
OMLAttributeData class >> readFrom: aStream [
<category: 'parsing'>
^ OMLAttributeData new
data: (aStream next: (self parseLength: aStream));
yourself
]
data [
<category: 'parsing'>
^ data
]
data: aData [
<category: 'parsing'>
data := aData
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putLen16: data size;
putByteArray: data.
]
writeOn: aMsg with: attr [
attr hasLength
ifTrue: [aMsg putLen16: data size].
aMsg putByteArray: data.
]
asOMLAttributeData [
<category: 'conversion'>
^ self
]
]
OMLAttribute subclass: OMLSWConfiguration [
| sw_descriptions |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 SW Configuration'>
OMLSWConfiguration class >> attributeType [
<category: 'parsing'>
^ self attrSWConfiguration
]
OMLSWConfiguration class >> readFrom: aStream [
| res data len |
<category: 'parsing'>
res := self new.
len := self parseLength: aStream.
data := (aStream next: len) readStream.
[data atEnd] whileFalse: [
| tag |
tag := data next.
tag = OMLSWDescription attributeType
ifFalse: [^self error: 'OMLSWDescription wanted but got: ', tag asString].
res add: (OMLSWDescription readFrom: data).
].
^ res
]
swDescriptions [
<category: 'accessing'>
^ sw_descriptions ifNil:[sw_descriptions := OrderedCollection new]
]
add: aDesc [
<category: 'creation'>
self swDescriptions add: aDesc.
]
writeOn: aMsg [
| data |
data := Osmo.MessageBuffer new.
"Prepent the tag"
self swDescriptions do: [:each |
each writeWithTag: data.
].
aMsg
putLen16: data size;
putByteArray: data asByteArray.
]
]
OMLAttribute subclass: OMLSWDescription [
| file_id file_version |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 SW Description'>
OMLSWDescription class >> attributeType [
<category: 'parsing'>
^ self attrSWDescription
]
OMLSWDescription class >> readFrom: aStream [
| res tag len |
res := OMLSWDescription new.
"Read the file id"
(tag := aStream next) = self attrFileId
ifFalse: [^self error: 'FileID expected but got: ', tag asString].
len := ((aStream next: 2) asByteArray ushortAt: 1) swap16.
res fileId: (aStream next: len).
"Read the file version"
(tag := aStream next) = self attrFileVersion
ifFalse: [^self error: 'FileVersion expected but got: ', tag asString].
len := ((aStream next: 2) asByteArray ushortAt: 1) swap16.
res fileVersion: (aStream next: len).
^ res
]
fileId: anId [
<category: 'creation'>
file_id := anId
]
fileVersion: aVersion [
file_version := aVersion
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putByte: self class attrFileId;
putLen16: file_id size;
putByteArray: file_id.
aMsg
putByte: self class attrFileVersion;
putLen16: file_version size;
putByteArray: file_version.
]
]
OMLAttribute subclass: OMLChannelCombination [
| comb |
<category: 'BTS-OML'>
<comment: 'I represent a GSM 12.21 Channel Combination'>
Names := nil.
OMLChannelCombination class >> attributeType [
<category: 'parsing'>
^ self attrChannelCombination
]
OMLChannelCombination class >> readFrom: aStream [
<category: 'parsing'>
^ self new
combination: aStream next;
yourself
]
OMLChannelCombination class [
chanTCHF [ <category: 'coding'> ^ 16r00 ]
chanTCHH [ <category: 'coding'> ^ 16r01 ]
chanTCHH2 [ <category: 'coding'> ^ 16r02 ]
chanSDCCH [ <category: 'coding'> ^ 16r03 ]
chanMainBCCH [ <category: 'coding'> ^ 16r04 ]
chanBCCHComb [ <category: 'coding'> ^ 16r05 ]
chanBCCH [ <category: 'coding'> ^ 16r06 ]
chanBCCHWithCBCH [ <category: 'coding'> ^ 16r07 ]
chanSDCCHWithCBCH [ <category: 'coding'> ^ 16r08 ]
chanPDCH [ <category: 'coding'> ^ 16r0D ]
]
OMLChannelCombination class >> channelNames [
^ Names ifNil: [
Names := LookupTable new.
self class methodDictionary keysAndValuesDo: [:key :value |
value descriptor category = 'coding'
ifTrue: [
Names at: (self perform: key) put: key]]. Names]
]
combination: aCom [
<category: 'creation'>
comb := aCom
]
writeOn: aMsg [
<category: 'serialization'>
aMsg putByte: comb
]
]
Object subclass: OMLMessageBase [
<category: 'BTS-OML'>
<comment: 'I am the base of OML messages'>
OMLMessageBase class [
fomType [
<category: 'attributes'>
^ 16r80
]
placementOnly [
<category: 'placement-indicator'>
^ 16r80
]
objectClassSiteManager [
<category: 'object-class'>
^ 16r0
]
objectClassBTS [
<category: 'object-class'>
^ 16r1
]
objectClassRadioCarrier [
<category: 'object-class'>
^ 16r2
]
objectClassBasebandTransceiver [
<category: 'object-class'>
^ 16r4
]
objectClassChannel [
<category: 'object-class'>
^ 16r3
]
objectClassNull [
<category: 'object-class'>
^ 16rFF
]
msgStateChangedEventReport [
<category: 'message-type'>
^ 16r61
]
msgSWActivateRequest [
<category: 'message-type'>
^ 16r0A
]
msgSWActivateRequestAck [
<category: 'message-type'>
^ 16r0B
]
msgSWActivatedReport [
<category: 'message-type'>
^ 16r10
]
msgActivateSoftware [
<category: 'message-type'>
^ 16r0D
]
msgActivateSoftwareAck [
<category: 'message-type'>
^ 16r0E
]
msgActivateSoftwareNack [
<category: 'message-type'>
^ 16r0F
]
msgOpstart [
<category: 'message-type'>
^ 16r74
]
msgOpstartAck [
<category: 'message-type'>
^ 16r75
]
msgOpstartNack [
<category: 'message-type'>
^ 16r76
]
msgSetBTSAttributes [
<category: 'message-type'>
^ 16r41
]
msgSetBTSAttributesAck [
<category: 'message-type'>
^ 16r42
]
msgSetBTSAttributesNack [
<category: 'message-type'>
^ 16r43
]
msgChangeAdminState [
<category: 'message-type'>
^ 16r69
]
msgChangeAdminStateAck [
<category: 'message-type'>
^ 16r6A
]
msgChangeAdminStateNack [
<category: 'message-type'>
^ 16r6B
]
msgSetRadioCarrierAttributes [
<category: 'message-type'>
^ 16r44
]
msgSetRadioCarrierAttributesAck [
<category: 'message-type'>
^ 16r45
]
msgSetRadioCarrierAttributesNack [
<category: 'message-type'>
^ 16r46
]
msgSetChannelAttributes [
<category: 'message-type'>
^ 16r47
]
msgSetChannelAttributesAck [
<category: 'message-type'>
^ 16r48
]
msgSetChannelAttributesNack [
<category: 'message-type'>
^ 16r49
]
msgGetAttributes [
<category: 'message-type'>
^ 16r81
]
]
OMLMessageBase class >> parse: aStream [
| type |
<category: 'parsing'>
type := aStream next.
self allSubclassesDo: [:each |
each msgType = type
ifTrue: [^each readFrom: aStream]
].
self error: 'Can not handle type: ', type asString.
]
]
OMLMessageBase subclass: FOMMessage [
| om_field |
<category: 'BTS-OML'>
<comment: 'I represent a Formatted O&M message'>
FOMMessage class >> msgType [
<category: 'parsing'>
^ self fomType
]
FOMMessage class >> readFrom: aStream [
| placement seq len dataStream type |
<category: 'parsing'>
"Sanity checking"
(placement := aStream next) = self placementOnly
ifFalse: [^self error: 'Can not deal with fragmented OML'].
(seq := aStream next) = 0
ifFalse: [^self error: 'Can not deal with sequence numbers'].
"Prepare a new buffer"
len := aStream next.
dataStream := (aStream next: len) readStream.
type := dataStream next.
"Parse the O&M DataField now"
OMLDataField allSubclassesDo: [:each |
(each canHandle: type) ifTrue: [
^self new
omDataField: (each readFrom: dataStream);
yourself]].
^ self error: 'Can not parse O&M Data field type: ', type asString.
]
omDataField [
<category: 'creation'>
^ om_field
]
omDataField: aField [
<category: 'creation'>
om_field := aField
]
writeOn: aMsg [
| msg |
<category: 'serialize'>
msg := om_field toMessage asByteArray.
aMsg
putByte: self class msgType;
putByte: self class placementOnly;
putByte: 0;
putByte: msg size;
putByteArray: msg.
]
createAck [
<category: 'acking'>
"Try to create an ACK"
^ self class new
omDataField: om_field createAck;
yourself
]
createNack [
<category: 'acking'>
^ self class new
omDataField: om_field createNack.
]
createResponse: aResponse [
<category: 'acking'>
^ aResponse
ifTrue: [self createAck]
ifFalse: [self createNack].
]
]
Osmo.TLVParserBase subclass: OMLDataField [
| object_class object_instance |
OMLDataField class >> canHandle: aType [
<category: 'parsing'>
^ self attributeType = aType
]
OMLDataField class >> readFrom: aStream [
| oml |
<category: 'parsing'>
"Generic TLV parsing"
oml := self new
objectClass: aStream next;
objectInstance: (FOMObjectInstance readFrom: aStream);
yourself.
"Now parse all fields"
self tlvDescription do: [:each | | tag |
tag := aStream peek.
each isMandatory ifTrue: [
oml parseMandatory: each tag: tag stream: aStream.
].
each isOptional ifTrue: [
oml parseOptional: each tag: tag stream: aStream.
].
].
"done"
^ aStream atEnd
ifTrue: [oml]
ifFalse: [aStream upToEnd asByteArray printNl. oml inspect. self error: 'Not all bytes consumed.'].
]
objectClass: aClass [
<category: 'creation'>
object_class := aClass
]
objectInstance: anInstance [
<category: 'creation'>
object_instance := anInstance
]
objectClass [
<category: 'parsing'>
^ object_class
]
objectInstance [
<category: 'parsing'>
^ object_instance
]
writeHeaderOn: aMsg [
<category: 'serialize'>
"Write the type"
aMsg
putByte: self class attributeType;
putByte: object_class;
putByteArray: object_instance toMessage asByteArray.
]
]
OMLDataField subclass: OMLStateChangedEventReport [
| op_state av_status adm_state |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Datafield as of 8.8.1'>
OMLStateChangedEventReport class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgStateChangedEventReport
]
OMLStateChangedEventReport class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (OMLOperationalState asTLVDescription
beOptional;
instVarName: #op_state; yourself);
add: (OMLAvailabilityStatus asTLVDescription
beOptional;
instVarName: #av_status; yourself);
add: (OMLAdminState asTLVDescription
beOptional;
instVarName: #adm_state; yourself);
yourself
]
operationalState: aState [
<category: 'creation'>
op_state := aState
]
availabilityStatus: aStatus [
<category: 'creation'>
av_status := aStatus
]
administrativeState: aState [
<category: 'ipa-creation'>
"This is an extension and part of (older) GSM 12.21"
adm_state := aState.
]
]
OMLDataField subclass: OMLSWActivateRequest [
| hw_config sw_config |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.3.5'>
OMLSWActivateRequest class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSWActivateRequest.
]
OMLSWActivateRequest class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrHWConfiguration;
instVarName: #hw_config;
parseClass: OMLAttributeData;
yourself);
add: (OMLSWConfiguration asTLVDescription
instVarName: #sw_config; yourself);
yourself
]
hwConfiguration: aHWConfig [
<category: 'creation'>
hw_config := aHWConfig asOMLAttributeData.
]
swConfiguration: aSWConfig [
<category: 'creation'>
sw_config := aSWConfig
]
swConfiguration [
<category: 'accessing'>
^ sw_config
]
]
OMLSWActivateRequest subclass: OMLSWActivateRequestAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.3.5'>
OMLSWActivateRequestAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSWActivateRequestAck.
]
]
OMLDataField subclass: OMLActivateSoftware [
| sw_desc |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.3.6'>
OMLActivateSoftware class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgActivateSoftware
]
OMLActivateSoftware class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (OMLSWDescription asTLVDescription
beOptional;
instVarName: #sw_desc; yourself);
yourself
]
createAck [
<category: 'acking'>
^ OMLActivateSoftwareAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
swDescription: self swDescription;
yourself
]
swDescription [
<category: 'accessing'>
^ sw_desc
]
swDescription: aDesc [
<category: 'accessing'>
sw_desc := aDesc
]
]
OMLActivateSoftware subclass: OMLActivateSoftwareAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.3.6'>
OMLActivateSoftwareAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgActivateSoftwareAck
]
]
OMLDataField subclass: OMLSWActivatedReport [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.3.7'>
OMLSWActivatedReport class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSWActivatedReport
]
OMLSWActivatedReport class >> tlvDescription [
<category: 'parsing'>
^ #()
]
]
OMLDataField subclass: OMLOpstart [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.9.2'>
OMLOpstart class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgOpstart
]
OMLOpstart class >> tlvDescription [
<category: 'parsing'>
^ #()
]
createAck [
<category: 'acking'>
^ OMLOpstartAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
yourself
]
]
OMLOpstart subclass: OMLOpstartAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.9.2'>
OMLOpstartAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgOpstartAck
]
]
OMLDataField subclass: OMLSetBTSAttributes [
| inter_bounds intave con_fail t200 max_timing overload_period
ccch_threshold ccch_ind rach_busy rach_load bts_air ny1 bcch_arfcn
bsic time ipa_cgi ipa_paging |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.1'>
OMLSetBTSAttributes class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetBTSAttributes
]
bcchArfcn [
^ (bcch_arfcn data first bitShift: 8)
bitOr: bcch_arfcn data second.
]
OMLSetBTSAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrInterferenceLevelBoundaries;
beOptional; beTV; valueSize: 6;
instVarName: #inter_bounds; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrIntave;
beOptional; beTV; valueSize: 1;
instVarName: #intave; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrConnectionFailureCriterion;
beOptional;
instVarName: #con_fail; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrT200;
beOptional; beTV; valueSize: 7;
instVarName: #t200; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMaxTimingAdvance;
beOptional; beTV; valueSize: 1;
instVarName: #max_timing; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrOverloadPeriod;
beOptional;
instVarName: #overload_period; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrCCCHLoadThreshold;
beOptional; beTV; valueSize: 1;
instVarName: #ccch_threshold; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrCCCHLoadIndicationPeriod;
beOptional; beTV; valueSize: 1;
instVarName: #ccch_ind; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrRACHBusyThreshold;
beOptional; beTV; valueSize: 1;
instVarName: #rach_busy; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrRACHLoadAveragingSlots;
beOptional; beTV; valueSize: 2;
instVarName: #rach_load; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBTSAirTimer;
beOptional; beTV; valueSize: 1;
instVarName: #bts_air; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrNy1;
beOptional; beTV; valueSize: 1;
instVarName: #ny1; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBCCHArfcn;
beOptional; beTV; valueSize: 2;
instVarName: #bcch_arfcn; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBSIC;
beOptional; beTV; valueSize: 1;
instVarName: #bsic; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrStartingTime;
beOptional; beTV; valueSize: 2;
instVarName: #time; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: 16r8F; beOptional; instVarName: #ipa_paging;
parseClass: OMLAttributeData; yourself);
add: (Osmo.TLVDescription new
tag: 16r99; beOptional; instVarName: #ipa_cgi;
parseClass: OMLAttributeData; yourself);
yourself
]
createAck [
| ack |
<category: 'acking'>
ack := OMLSetBTSAttributesAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
yourself.
self class instVarNames do: [:name |
ack instVarNamed: name put: (self instVarNamed: name)].
^ ack
]
createNack [
| nack |
<category: 'acking'>
nack := OMLSetBTSAttributesNack new
objectClass: self objectClass;
objectInstance: self objectInstance;
yourself.
self class instVarNames do: [:name |
nack instVarNamed: name put: (self instVarNamed: name)].
^ nack
]
]
OMLSetBTSAttributes subclass: OMLSetBTSAttributesAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.1'>
OMLSetBTSAttributesAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetBTSAttributesAck
]
]
OMLSetBTSAttributes subclass: OMLSetBTSAttributesNack [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.1'>
OMLSetBTSAttributesNack class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetBTSAttributesNack
]
]
OMLDataField subclass: OMLChangeAdminState [
| adm_state |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.8.5'>
OMLChangeAdminState class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgChangeAdminState
]
OMLChangeAdminState class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (OMLAdminState asTLVDescription
instVarName: #adm_state; yourself);
yourself
]
adminState: aState [
<category: 'creation'>
adm_state := aState.
]
adminState [
<category: 'accessing'>
^ adm_state
]
createAck [
<category: 'acking'>
^ OMLChangeAdminStateAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
adminState: self adminState;
yourself.
]
]
OMLChangeAdminState subclass: OMLChangeAdminStateAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.8.5'>
OMLChangeAdminStateAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgChangeAdminStateAck
]
]
OMLDataField subclass: OMLSetRadioCarrierAttributes [
| max_power arfcn_list |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.2'>
OMLSetRadioCarrierAttributes class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetRadioCarrierAttributes
]
OMLSetRadioCarrierAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMaxPowerReduction;
beOptional; beTV; valueSize: 1;
instVarName: #max_power; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrARFCNList;
beOptional;
instVarName: #arfcn_list; parseClass: OMLAttributeData;
yourself);
yourself.
]
maxPower [
<category: 'accessing'>
^ max_power
]
maxPower: aPower [
<category: 'creation'>
max_power := aPower
]
arfcnList [
| list |
<category: 'arfcn_list'>
list := OrderedCollection new.
arfcn_list data size printNl.
"Collect the ARFCNs in the list. Always two together"
1 to: (arfcn_list data size - 1) by: 2 do: [:nr |
| hi low |
hi := arfcn_list data at: nr.
low := arfcn_list data at: nr + 1.
list add: ((hi bitShift: 8) bitOr: low).
].
^ list
]
arfcnList: aList [
<category: 'creation'>
arfcn_list := aList
]
createAck [
<category: 'acking'>
^ OMLSetRadioCarrierAttributesAck new
objectInstance: self objectInstance;
objectClass: self objectClass;
maxPower: max_power;
arfcnList: arfcn_list;
yourself
]
]
OMLSetRadioCarrierAttributes subclass: OMLSetRadioCarrierAttributesAck [
| max_power arfcn_list |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.2'>
OMLSetRadioCarrierAttributesAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetRadioCarrierAttributesAck
]
]
OMLDataField subclass: OMLSetChannelAttributes [
| chan_comb hsn maio arfcn_list time tsc |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.3'>
OMLSetChannelAttributes class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetChannelAttributes
]
OMLSetChannelAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (OMLChannelCombination asTLVDescription
beOptional;
instVarName: #chan_comb; yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrHSN; beOptional; beTV; valueSize: 1;
parseClass: OMLAttributeData;
instVarName: #hsn; yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMAIO; beOptional; beTV; valueSize: 1;
parseClass: OMLAttributeData;
instVarName: #maio; yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrARFCNList;
beOptional;
instVarName: #arfcn_list; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrStartingTime;
beOptional; beTV; valueSize: 2;
instVarName: #time; parseClass: OMLAttributeData;
yourself);
add: (Osmo.TLVDescription new
tag: OMLAttribute attrTSC;
beOptional; beTV; valueSize: 1;
instVarName: #tsc; parseClass: OMLAttributeData;
yourself);
yourself
]
channelCombination [
<category: 'accessing'>
^ chan_comb
]
createAck [
| ack |
<category: 'acking'>
ack := OMLSetChannelAttributesAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
yourself.
self class instVarNames do: [:name |
ack instVarNamed: name put: (self instVarNamed: name)].
^ ack
]
]
OMLSetChannelAttributes subclass: OMLSetChannelAttributesAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.6.3'>
OMLSetChannelAttributesAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgSetChannelAttributesAck
]
]
OMLDataField subclass: OMLGetAttributes [
| requestedAttributes |
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Get Attributes as of 8.11.1'>
OMLGetAttributes class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgGetAttributes
]
OMLGetAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrRequiredAttributes;
beTLV; minSize: 1;
parseClass: OMLAttributeData;
instVarName: #requestedAttributes; yourself);
yourself
]
]