" (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 . " PackageLoader fileInPackage: #OsmoNetwork. Iterable extend [ asOMLAttributeData [ ^ OMLAttributeData new data: self; yourself ] ] Object subclass: FOMObjectInstance [ | bts trx ts | FOMObjectInstance class >> readFrom: aStream [ | bts trx ts | ^ FOMObjectInstance new bts: aStream next; trx: aStream next; ts: aStream next; yourself ] bts: aBTS [ bts := aBTS ] trx: aTRX [ trx := aTRX ] ts: aTS [ ts := aTS ] bts: aBTS trx: aTRX ts: aTS [ bts := aBTS. trx := aTRX. ts := aTS. ] bts [ ^ bts ] trx [ ^ trx ] ts [ ^ ts ] writeOn: aMsg [ aMsg putByte: bts; putByte: trx; putByte: ts. ] = anInstance [ bts = anInstance bts ifFalse: [^false]. trx = anInstance trx ifFalse: [^false]. ts = anInstance ts ifFalse: [^false]. ^ true ] hash [ ^ ((bts bitShift: 16) + (trx bitShift: 8) + ts) hash ] ] Object subclass: OMLAttribute [ | attrName default | OMLAttribute class [ name: aName [ ^ self new attributeName: aName; yourself ] name: aName default: aDefault [ ^ self new attributeName: aName; default: aDefault; yourself ] attrOperationalState [ ^ 16r24 ] attrAvailabilityStatus [ ^ 16r07 ] attrAdministrativeState [ ^ 16r04 ] attrSWConfiguration [ ^ 16r41 ] attrSWDescription [ ^ 16r42 ] attrHWConfiguration [ ^ 16r16 ] attrFileId [ ^ 16r12 ] attrFileVersion [ ^ 16r13 ] attrInterferenceLevelBoundaries [ ^ 16r19 ] attrIntave [ ^ 16r18 ] attrConnectionFailureCriterion [ ^ 16r0E ] attrT200 [ ^ 16r33 ] attrMaxTimingAdvance [ ^ 16r1F ] attrOverloadPeriod [ ^ 16r25 ] attrCCCHLoadThreshold [ ^ 16r0C ] attrCCCHLoadIndicationPeriod [ ^ 16r0B ] attrRACHBusyThreshold [ ^ 16r2A ] attrRACHLoadAveragingSlots [ ^ 16r2B ] attrBTSAirTimer [ ^ 16r0A ] attrNy1 [ ^ 16r23 ] attrBCCHArfcn [ ^ 16r08 ] attrBSIC [ ^ 16r09 ] attrStartingTime [ ^ 16r32 ] attrMaxPowerReduction [ ^ 16r2D ] attrARFCNList [ ^ 16r05 ] attrChannelCombination [ ^ 16r0D ] attrHSN [ ^ 16r15 ] attrMAIO [ ^ 16r1B ] attrTSC [ ^ 16r40 ] attrRequiredAttributes [ ^ 16r1A ] asTLVDescription [ ^ Osmo.TLVDescription new parseClass: self; tag: self attributeType; yourself ] parseLength: aStream [ ^ ((aStream next: 2) asByteArray ushortAt: 1) swap16 ] readFrom: aStream with: anAttr [ ^ self readFrom: aStream ] ] attributeName: aName [ attrName := aName ] attributeName [ ^ attrName ] default: aDefault [ default := aDefault ] default [ ^ default ] writeWithTag: aMsg [ "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 | "TODO: This could be a list of states..." OMLOperationalState class >> attributeType [ ^ self attrOperationalState ] OMLOperationalState class [ disabledState [ ^ self new state: self disabled; yourself. ] disabled [ ^ 1 ] enabled [ ^ 2 ] null [ ^ 16rFF ] ] state [ ^ state ] state: aState [ state := aState. ] writeOn: aMsg [ aMsg putByte: state. ] ] OMLAttribute subclass: OMLAvailabilityStatus [ | state | OMLAvailabilityStatus class >> attributeType [ ^ self attrAvailabilityStatus ] OMLAvailabilityStatus class [ notInstalledState [ ^ self new state: self notInstalled; yourself. ] inTest [ ^ 0 ] failed [ ^ 1 ] powerOff [ ^ 2 ] offline [ ^ 3 ] dependency [ ^ 5 ] degraded[ ^ 6 ] notInstalled [ ^ 7 ] ] state [ ^ state ] state: aState [ state := aState. ] writeOn: aMsg [ state isNil ifTrue: [ aMsg putLen16: 0] ifFalse: [ aMsg putLen16: 1; putByte: state]. ] ] OMLAttribute subclass: OMLAdminState [ | state | OMLAdminState class >> attributeType [ ^ self attrAdministrativeState ] OMLAdminState class >> readFrom: aStream [ ^ self new state: aStream next; yourself ] OMLAdminState class [ lockedState [ ^ self new state: self locked; yourself ] locked [ ^ 16r01 ] unlocked [ ^ 16r02 ] shuttingDown [ ^ 16r03 ] notSupported [ ^ 16rFF ] ] state: aState [ state := aState. ] writeOn: aMsg [ aMsg putByte: state. ] ] OMLAttribute subclass: OMLAttributeData [ | data | OMLAttributeData class >> readFrom: aStream with: anAttr [ anAttr hasLength ifTrue: [^self readFrom: aStream]. ^ OMLAttributeData new data: (aStream next: anAttr valueSize); yourself ] OMLAttributeData class >> readFrom: aStream [ ^ OMLAttributeData new data: (aStream next: (self parseLength: aStream)); yourself ] data [ ^ data ] data: aData [ data := aData ] writeOn: aMsg [ aMsg putLen16: data size; putByteArray: data. ] writeOn: aMsg with: attr [ attr hasLength ifTrue: [aMsg putLen16: data size]. aMsg putByteArray: data. ] asOMLAttributeData [ ^ self ] ] OMLAttribute subclass: OMLSWConfiguration [ | sw_descriptions | OMLSWConfiguration class >> attributeType [ ^ self attrSWConfiguration ] OMLSWConfiguration class >> readFrom: aStream [ | res data len | 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 [ ^ sw_descriptions ifNil:[sw_descriptions := OrderedCollection new] ] add: aDesc [ 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 | OMLSWDescription class >> attributeType [ ^ 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 [ file_id := anId ] fileVersion: aVersion [ file_version := aVersion ] writeOn: aMsg [ 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 | Names := nil. OMLChannelCombination class >> attributeType [ ^ self attrChannelCombination ] OMLChannelCombination class >> readFrom: aStream [ ^ self new combination: aStream next; yourself ] OMLChannelCombination class [ chanTCHF [ ^ 16r00 ] chanTCHH [ ^ 16r01 ] chanTCHH2 [ ^ 16r02 ] chanSDCCH [ ^ 16r03 ] chanMainBCCH [ ^ 16r04 ] chanBCCHComb [ ^ 16r05 ] chanBCCH [ ^ 16r06 ] chanBCCHWithCBCH [ ^ 16r07 ] chanSDCCHWithCBCH [ ^ 16r08 ] chanPDCH [ ^ 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 [ comb := aCom ] writeOn: aMsg [ aMsg putByte: comb ] ] Object subclass: OMLMessageBase [ OMLMessageBase class [ fomType [ ^ 16r80 ] placementOnly [ ^ 16r80 ] objectClassSiteManager [ ^ 16r0 ] objectClassBTS [ ^ 16r1 ] objectClassRadioCarrier [ ^ 16r2 ] objectClassBasebandTransceiver [ ^ 16r4 ] objectClassChannel [ ^ 16r3 ] objectClassNull [ ^ 16rFF ] msgStateChangedEventReport [ ^ 16r61 ] msgSWActivateRequest [ ^ 16r0A ] msgSWActivateRequestAck [ ^ 16r0B ] msgSWActivatedReport [ ^ 16r10 ] msgActivateSoftware [ ^ 16r0D ] msgActivateSoftwareAck [ ^ 16r0E ] msgActivateSoftwareNack [ ^ 16r0F ] msgOpstart [ ^ 16r74 ] msgOpstartAck [ ^ 16r75 ] msgOpstartNack [ ^ 16r76 ] msgSetBTSAttributes [ ^ 16r41 ] msgSetBTSAttributesAck [ ^ 16r42 ] msgSetBTSAttributesNack [ ^ 16r43 ] msgChangeAdminState [ ^ 16r69 ] msgChangeAdminStateAck [ ^ 16r6A ] msgChangeAdminStateNack [ ^ 16r6B ] msgSetRadioCarrierAttributes [ ^ 16r44 ] msgSetRadioCarrierAttributesAck [ ^ 16r45 ] msgSetRadioCarrierAttributesNack [ ^ 16r46 ] msgSetChannelAttributes [ ^ 16r47 ] msgSetChannelAttributesAck [ ^ 16r48 ] msgSetChannelAttributesNack [ ^ 16r49 ] msgGetAttributes [ ^ 16r81 ] ] OMLMessageBase class >> parse: aStream [ | type | 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 | FOMMessage class >> msgType [ ^ self fomType ] FOMMessage class >> readFrom: aStream [ | placement seq len dataStream type | "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 [ ^ om_field ] omDataField: aField [ om_field := aField ] writeOn: aMsg [ | msg | msg := om_field toMessage asByteArray. aMsg putByte: self class msgType; putByte: self class placementOnly; putByte: 0; putByte: msg size; putByteArray: msg. ] createAck [ "Try to create an ACK" ^ self class new omDataField: om_field createAck; yourself ] createNack [ ^ self class new omDataField: om_field createNack. ] createResponse: aResponse [ ^ aResponse ifTrue: [self createAck] ifFalse: [self createNack]. ] ] Osmo.TLVParserBase subclass: OMLDataField [ | object_class object_instance | OMLDataField class >> canHandle: aType [ ^ self attributeType = aType ] OMLDataField class >> readFrom: aStream [ | oml | "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 [ object_class := aClass ] objectInstance: anInstance [ object_instance := anInstance ] objectClass [ ^ object_class ] objectInstance [ ^ object_instance ] writeHeaderOn: aMsg [ "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 | OMLStateChangedEventReport class >> attributeType [ ^ FOMMessage msgStateChangedEventReport ] OMLStateChangedEventReport class >> tlvDescription [ ^ 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 [ op_state := aState ] availabilityStatus: aStatus [ av_status := aStatus ] administrativeState: aState [ "This is an extension and part of (older) GSM 12.21" adm_state := aState. ] ] OMLDataField subclass: OMLSWActivateRequest [ | hw_config sw_config | OMLSWActivateRequest class >> attributeType [ ^ FOMMessage msgSWActivateRequest. ] OMLSWActivateRequest class >> tlvDescription [ ^ 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 [ hw_config := aHWConfig asOMLAttributeData. ] swConfiguration: aSWConfig [ sw_config := aSWConfig ] swConfiguration [ ^ sw_config ] ] OMLSWActivateRequest subclass: OMLSWActivateRequestAck [ OMLSWActivateRequestAck class >> attributeType [ ^ FOMMessage msgSWActivateRequestAck. ] ] OMLDataField subclass: OMLActivateSoftware [ | sw_desc | OMLActivateSoftware class >> attributeType [ ^ FOMMessage msgActivateSoftware ] OMLActivateSoftware class >> tlvDescription [ ^ OrderedCollection new add: (OMLSWDescription asTLVDescription beOptional; instVarName: #sw_desc; yourself); yourself ] createAck [ ^ OMLActivateSoftwareAck new objectClass: self objectClass; objectInstance: self objectInstance; swDescription: self swDescription; yourself ] swDescription [ ^ sw_desc ] swDescription: aDesc [ sw_desc := aDesc ] ] OMLActivateSoftware subclass: OMLActivateSoftwareAck [ OMLActivateSoftwareAck class >> attributeType [ ^ FOMMessage msgActivateSoftwareAck ] ] OMLDataField subclass: OMLSWActivatedReport [ OMLSWActivatedReport class >> attributeType [ ^ FOMMessage msgSWActivatedReport ] OMLSWActivatedReport class >> tlvDescription [ ^ #() ] ] OMLDataField subclass: OMLOpstart [ OMLOpstart class >> attributeType [ ^ FOMMessage msgOpstart ] OMLOpstart class >> tlvDescription [ ^ #() ] createAck [ ^ OMLOpstartAck new objectClass: self objectClass; objectInstance: self objectInstance; yourself ] ] OMLOpstart subclass: OMLOpstartAck [ OMLOpstartAck class >> attributeType [ ^ 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 | OMLSetBTSAttributes class >> attributeType [ ^ FOMMessage msgSetBTSAttributes ] bcchArfcn [ ^ (bcch_arfcn data first bitShift: 8) bitOr: bcch_arfcn data second. ] OMLSetBTSAttributes class >> tlvDescription [ ^ 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 | 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 | 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 [ OMLSetBTSAttributesAck class >> attributeType [ ^ FOMMessage msgSetBTSAttributesAck ] ] OMLSetBTSAttributes subclass: OMLSetBTSAttributesNack [ OMLSetBTSAttributesNack class >> attributeType [ ^ FOMMessage msgSetBTSAttributesNack ] ] OMLDataField subclass: OMLChangeAdminState [ | adm_state | OMLChangeAdminState class >> attributeType [ ^ FOMMessage msgChangeAdminState ] OMLChangeAdminState class >> tlvDescription [ ^ OrderedCollection new add: (OMLAdminState asTLVDescription instVarName: #adm_state; yourself); yourself ] adminState: aState [ adm_state := aState. ] adminState [ ^ adm_state ] createAck [ ^ OMLChangeAdminStateAck new objectClass: self objectClass; objectInstance: self objectInstance; adminState: self adminState; yourself. ] ] OMLChangeAdminState subclass: OMLChangeAdminStateAck [ OMLChangeAdminStateAck class >> attributeType [ ^ FOMMessage msgChangeAdminStateAck ] ] OMLDataField subclass: OMLSetRadioCarrierAttributes [ | max_power arfcn_list | OMLSetRadioCarrierAttributes class >> attributeType [ ^ FOMMessage msgSetRadioCarrierAttributes ] OMLSetRadioCarrierAttributes class >> tlvDescription [ ^ 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 [ ^ max_power ] maxPower: aPower [ max_power := aPower ] arfcnList [ | 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 [ arfcn_list := aList ] createAck [ ^ OMLSetRadioCarrierAttributesAck new objectInstance: self objectInstance; objectClass: self objectClass; maxPower: max_power; arfcnList: arfcn_list; yourself ] ] OMLSetRadioCarrierAttributes subclass: OMLSetRadioCarrierAttributesAck [ | max_power arfcn_list | OMLSetRadioCarrierAttributesAck class >> attributeType [ ^ FOMMessage msgSetRadioCarrierAttributesAck ] ] OMLDataField subclass: OMLSetChannelAttributes [ | chan_comb hsn maio arfcn_list time tsc | OMLSetChannelAttributes class >> attributeType [ ^ FOMMessage msgSetChannelAttributes ] OMLSetChannelAttributes class >> tlvDescription [ ^ 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 [ ^ chan_comb ] createAck [ | ack | 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 [ OMLSetChannelAttributesAck class >> attributeType [ ^ FOMMessage msgSetChannelAttributesAck ] ] OMLDataField subclass: OMLGetAttributes [ | requestedAttributes | OMLGetAttributes class >> attributeType [ ^ FOMMessage msgGetAttributes ] OMLGetAttributes class >> tlvDescription [ ^ OrderedCollection new add: (Osmo.TLVDescription new tag: OMLAttribute attrRequiredAttributes; beTLV; minSize: 1; parseClass: OMLAttributeData; instVarName: #requestedAttributes; yourself); yourself ] ]