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

1430 lines
51 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: #OsmoGSM.
Iterable extend [
asRSLAttributeData [
<category: '*-BTS-OML-Msg'>
^ RSLAttributeData new
data: self; yourself
]
]
Osmo.TLVDescription class extend [
newRSLDescription [
<category: '*-BTS-RSL-Msg'>
^self new
beForceTagged;
yourself
]
]
Osmo.TLVParserBase subclass: RSLMessageBase [
<category: 'BTS-RSL'>
<comment: 'I am the base of all RSL messages. I follow GSM 08.58'>
RSLMessageBase class [
| messageType messageDefinition |
messageType [
<category: 'tlv'>
^ self perform: messageType
]
tlvDescription [
<category: 'tlv'>
^ RSLMessageDefinitions perform: messageDefinition
]
rslMessageType: aType [
<category: 'init'>
messageType := aType asSymbol
]
rslMessageDefinition: aDef [
messageDefinition := aDef asSymbol
]
]
RSLMessageBase class [
discriminatorMask [ <category: 'discriminator'> ^ 2r11111110 ]
discriminatorReserved [ <category: 'discriminator'> ^ 2r0000000 ]
discriminatorRadioLink [ <category: 'discriminator'> ^ 2r0000001 ]
discriminatorDedicated [ <category: 'discriminator'> ^ 2r0000100 ]
discriminatorCommon [ <category: 'discriminator'> ^ 2r0000110 ]
discriminatorTRX [ <category: 'discriminator'> ^ 2r0001000 ]
discriminatorLCS [ <category: 'discriminator'> ^ 2r0010000 ]
]
RSLMessageBase class [
messageRadioLinkMask [ <category: 'msg-radio-link'> ^ 2r00001111 ]
messageRadioLinkDataRequest [ <category: 'msg-radio-link'> ^ 2r00000001 ]
messageRadioLinkDataIndication [ <category: 'msg-radio-link'> ^ 2r00000010 ]
messageRadioLinkErrorIndication [ <category: 'msg-radio-link'> ^ 2r00000011 ]
messageRadioLinkEstablishRequest [ <category: 'msg-radio-link'> ^ 2r00000100 ]
messageRadioLinkEstablishConfirm [ <category: 'msg-radio-link'> ^ 2r00000101 ]
messageRadioLinkEstablishIndication [ <category: 'msg-radio-link'> ^ 2r00000110 ]
messageRadioLinkReleaseRequest [ <category: 'msg-radio-link'> ^ 2r00000111 ]
messageRadioLinkReleaseConfirm [ <category: 'msg-radio-link'> ^ 2r00001000 ]
messageRadioLinkReleaseIndication [ <category: 'msg-radio-link'> ^ 2r00001001 ]
messageRadioLinkUnitDataRequest [ <category: 'msg-radio-link'> ^ 2r00001010 ]
messageRadioLinkUnitDataIndication [ <category: 'msg-radio-link'> ^ 2r00001011 ]
messageTrxMask [ <category: 'msg-trx-mgmnt'> ^ 2r00011111 ]
messageTrxBcchInformation [ <category: 'msg-trx-mgmnt'> ^ 2r00010001 ]
messageTrxCcchLoadIndication [ <category: 'msg-trx-mgmnt'> ^ 2r00010010 ]
messageTrxChannelRequired [ <category: 'msg-trx-mgmnt'> ^ 2r00010011 ]
messageTrxDeletingIndication [ <category: 'msg-trx-mgmnt'> ^ 2r00010100 ]
messageTrxPagingCommand [ <category: 'msg-trx-mgmnt'> ^ 2r00010101 ]
messageTrxImmediateAssignCommand [ <category: 'msg-trx-mgmnt'> ^ 2r00010110 ]
messageTrxSmsBroadcastRequest [ <category: 'msg-trx-mgmnt'> ^ 2r00010111 ]
messageTrxRfResourceIndication [ <category: 'msg-trx-mgmnt'> ^ 2r00011001 ]
messageTrxSacchFilling [ <category: 'msg-trx-mgmnt'> ^ 2r00011010 ]
messageTrxOverload [ <category: 'msg-trx-mgmnt'> ^ 2r00011011 ]
messageTrxErrorReport [ <category: 'msg-trx-mgmnt'> ^ 2r00011100 ]
messageTrxSmsBroadcastCommand [ <category: 'msg-trx-mgmnt'> ^ 2r00011101 ]
messageTrxCbchLoadIndication [ <category: 'msg-trx-mgmnt'> ^ 2r00011110 ]
messageTrxNotificationCommand [ <category: 'msg-trx-mgmnt'> ^ 2r00011111 ]
messageDedChannelActication [ <category: 'msg-ded-mgmnt'> ^ 2r00100001 ]
messageDedChannelActivationAck [ <category: 'msg-ded-mgmnt'> ^ 2r00100010 ]
messageDedChannelActivationNack [ <category: 'msg-ded-mgmnt'> ^ 2r00100011 ]
messageDedConnectionFailure [ <category: 'msg-ded-mgmnt'> ^ 2r00100100 ]
messageDedDeactivateSacch [ <category: 'msg-ded-mgmnt'> ^ 2r00100101 ]
messageDedEncryptionCommand [ <category: 'msg-ded-mgmnt'> ^ 2r00100110 ]
messageDedHandoverDetection [ <category: 'msg-ded-mgmnt'> ^ 2r00100111 ]
messageDedMeasurementResult [ <category: 'msg-ded-mgmnt'> ^ 2r00101000 ]
messageDedModeModifyRequest [ <category: 'msg-ded-mgmnt'> ^ 2r00101001 ]
messageDedModeModifyAck [ <category: 'msg-ded-mgmnt'> ^ 2r00101010 ]
messageDedModeModifyNack [ <category: 'msg-ded-mgmnt'> ^ 2r00101011 ]
messageDedPhysicalContextRequest [ <category: 'msg-ded-mgmnt'> ^ 2r00101100 ]
messageDedPhysicalContextConfirm [ <category: 'msg-ded-mgmnt'> ^ 2r00101101 ]
messageDedRfChannelRelease [ <category: 'msg-ded-mgmnt'> ^ 2r00101110 ]
messageDedMsPowerControl [ <category: 'msg-ded-mgmnt'> ^ 2r00101111 ]
messageDedBsPowerControl [ <category: 'msg-ded-mgmnt'> ^ 2r00110000 ]
messageDedPreprocessConfigure [ <category: 'msg-ded-mgmnt'> ^ 2r00110001 ]
messageDedPreprocessedMeasureResult [ <category: 'msg-ded-mgmnt'> ^ 2r00110010 ]
messageDedRfChannelReleaseAck [ <category: 'msg-ded-mgmnt'> ^ 2r00110011 ]
messageDedSacchInfoModify [ <category: 'msg-ded-mgmnt'> ^ 2r00110100 ]
messageDedTalkerDetection [ <category: 'msg-ded-mgmnt'> ^ 2r00110101 ]
messageDedListenerDetection [ <category: 'msg-ded-mgmnt'> ^ 2r00110110 ]
messageDedRemoteCodecConfigReport [ <category: 'msg-ded-mgmnt'> ^ 2r00110111 ]
messageDedRoundTripDelayReport [ <category: 'msg-ded-mgmnt'> ^ 2r00111000 ]
messageDedPreHandOverNotification [ <category: 'msg-ded-mgmnt'> ^ 2r00111001 ]
messageDedMultirateCodecModRequest [ <category: 'msg-ded-mgmnt'> ^ 2r00111010 ]
messageDedMultirateCodecModAck [ <category: 'msg-ded-mgmnt'> ^ 2r00111011 ]
messageDedMultirateCodecModNack [ <category: 'msg-ded-mgmnt'> ^ 2r00111100 ]
messageDedMultirateCodedModPerformed[ <category: 'msg-ded-mgmnt'> ^ 2r00111101 ]
messageDedTfoReport [ <category: 'msg-ded-mgmnt'> ^ 2r00111110 ]
messageDedTfoModificationRequest [ <category: 'msg-ded-mgmnt'> ^ 2r00111111 ]
]
RSLMessageBase class >> parse: aStream [
| discrim transp type |
<category: 'parsing'>
transp := aStream peek bitAnd: 2r1.
discrim := aStream next bitShift: -1.
type := aStream next.
self allSubclassesDo: [:each |
(each canHandle: discrim transparent: transp type: type) ifTrue: [
| res |
res := each readFrom: aStream.
aStream atEnd ifFalse: [
aStream upToEnd printNl.
^self error: 'Message was not fully parsed.'].
^ res.
].
].
^ self error: 'Did not find a handler for messgae type: ', type displayString.
]
RSLMessageBase class >> ignoredBaseClasses [
<category: 'handling'>
^ {RSLCommonChannelManagement. RSLTRXManagement.
RSLDedicatedChannelManagement. RSLRadioLinkManagement. RSLIPAVendorManagement}
]
RSLMessageBase class >> canHandle: aDiscrim transparent: aTrans type: aType [
<category: 'parsing'>
"Ignore the common base classes."
(self ignoredBaseClasses includes: self)
ifTrue: [^false].
"Check if discriminator, transparency (asnumber) and messageType match"
aDiscrim = self messageDiscrimator
ifFalse: [^false].
aTrans = self isTransparent
ifFalse: [^false].
aType = self messageType
ifFalse: [^false].
^ true.
]
RSLMessageBase class >> readFrom: aStream [
| rsl |
<category: 'parsing'>
rsl := self new.
self tlvDescription do: [:each | | tag |
tag := aStream peek.
each isMandatory
ifTrue: [rsl parseMandatory: each tag: tag stream: aStream].
each isConditional
ifTrue: [rsl parseConditional: each tag: tag stream: aStream].
each isOptional
ifTrue: [rsl parseOptional: each tag: tag stream: aStream].
].
^ rsl.
]
writeHeaderOn: aMsg [
| disc |
<category: 'serialize'>
disc := self class messageDiscrimator bitShift: 1.
disc := disc bitOr: self class isTransparent.
aMsg
putByte: disc;
putByte: self class messageType.
]
]
Object subclass: RSLInformationElement [
<category: 'BTS-RSL'>
<comment: 'I represent the base class of all RSL IEs'>
RSLInformationElement class [
attrChannelNumber [ <category: 'ie'> ^ 2r00000001 ]
attrLinkIdentifier [ <category: 'ie'> ^ 2r00000010 ]
attrActivationType [ <category: 'ie'> ^ 2r00000011 ]
attrBSPower [ <category: 'ie'> ^ 2r00000100 ]
attrChannelIdentification [ <category: 'ie'> ^ 2r00000101 ]
attrChannelMode [ <category: 'ie'> ^ 2r00000110 ]
attrEncryptionInformation [ <category: 'ie'> ^ 2r00000111 ]
attrFrameNumber [ <category: 'ie'> ^ 2r00001000 ]
attrHandoverReference [ <category: 'ie'> ^ 2r00001001 ]
attrL1Information [ <category: 'ie'> ^ 2r00001010 ]
attrL3Information [ <category: 'ie'> ^ 2r00001011 ]
attrMSIdentifty [ <category: 'ie'> ^ 2r00001100 ]
attrMSPower [ <category: 'ie'> ^ 2r00001101 ]
attrPagingGroup [ <category: 'ie'> ^ 2r00001110 ]
attrPagingLoad [ <category: 'ie'> ^ 2r00001111 ]
attrPhysicalContext [ <category: 'ie'> ^ 2r00010000 ]
attrAccessDelay [ <category: 'ie'> ^ 2r00010001 ]
attrRACHLoad [ <category: 'ie'> ^ 2r00010010 ]
attrRequestReference [ <category: 'ie'> ^ 2r00010011 ]
attrReleaseMode [ <category: 'ie'> ^ 2r00010100 ]
attrResourceInformation [ <category: 'ie'> ^ 2r00010101 ]
attrRLMCause [ <category: 'ie'> ^ 2r00010110 ]
attrStartingTime [ <category: 'ie'> ^ 2r00010111 ]
attrTimingAdvance [ <category: 'ie'> ^ 2r00011000 ]
attrUplinkMeasurements [ <category: 'ie'> ^ 2r00011001 ]
attrCause [ <category: 'ie'> ^ 2r00011010 ]
attrMeasurementResultNumber [ <category: 'ie'> ^ 2r00011011 ]
attrMessageIdentifier [ <category: 'ie'> ^ 2r00011100 ]
attrReserved1 [ <category: 'ie'> ^ 2r00011101 ]
attrSystemInfoType [ <category: 'ie'> ^ 2r00011110 ]
attrMSPowerParameters [ <category: 'ie'> ^ 2r00011111 ]
attrBSPowerParameters [ <category: 'ie'> ^ 2r00100000 ]
attrPreprocessingParameters [ <category: 'ie'> ^ 2r00100001 ]
attrPreprocessingMeasurements [ <category: 'ie'> ^ 2r00100010 ]
attrReserved2 [ <category: 'ie'> ^ 2r00100011 ]
attrSmsCBInformation [ <category: 'ie'> ^ 2r00100100 ]
attrMsTimingOffset [ <category: 'ie'> ^ 2r00100101 ]
attrErroneousMeasure [ <category: 'ie'> ^ 2r00100110 ]
attrFullBcchInformation [ <category: 'ie'> ^ 2r00100111 ]
attrChannelNeeded [ <category: 'ie'> ^ 2r00101000 ]
attrCbCommandType [ <category: 'ie'> ^ 2r00101001 ]
attrSmsCbMessage [ <category: 'ie'> ^ 2r00101010 ]
attrFullImmediateAssignInfo [ <category: 'ie'> ^ 2r00101011 ]
attrSacchInformation [ <category: 'ie'> ^ 2r00101100 ]
attrCbchLoadInformation [ <category: 'ie'> ^ 2r00101101 ]
attrSmsCbChannelIndicator [ <category: 'ie'> ^ 2r00101110 ]
attrGroupCallReference [ <category: 'ie'> ^ 2r00101111 ]
attrChannelDescription [ <category: 'ie'> ^ 2r00110000 ]
attrNchDrxInformation [ <category: 'ie'> ^ 2r00110001 ]
attrCommandIndicator [ <category: 'ie'> ^ 2r00110010 ]
attreMLPPPriority [ <category: 'ie'> ^ 2r00110011 ]
attrUIC [ <category: 'ie'> ^ 2r00110100 ]
attrMainChannelReference [ <category: 'ie'> ^ 2r00110101 ]
attrMultiRateConfiguration [ <category: 'ie'> ^ 2r00110110 ]
attrMultiRateControl [ <category: 'ie'> ^ 2r00110111 ]
attrSupportedCodecTypes [ <category: 'ie'> ^ 2r00111000 ]
attrCodecConfiguration [ <category: 'ie'> ^ 2r00111001 ]
attrRoundTripDelay [ <category: 'ie'> ^ 2r00111010 ]
attrTFOStatus [ <category: 'ie'> ^ 2r00111011 ]
attrLLPAPDU [ <category: 'ie'> ^ 2r00111100 ]
]
]
Object subclass: RSLMessageDefinitions [
<category: 'BTS-RSL'>
<comment: 'I represent all TLV descriptions for (all) RSL messages.'>
RSLMessageDefinitions class [
channelNumberIE [
<category: 'common-ie'>
^ Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrChannelNumber;
instVarName: #channel_number; parseClass: RSLChannelNumber;
beTV; valueSize: 1; yourself.
]
linkIdentifierIE [
<category: 'common-ie'>
^ Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrLinkIdentifier;
instVarName: #link_id; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself
]
l3InfoIE [
<category: 'common-ie'>
^Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beTLV; beLen16; yourself
]
causeIE [
<category: 'common-ie'>
^ Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrCause;
instVarName: #cause; parseClass: RSLAttributeData;
beTLV; minSize: 1; yourself
]
radioLinkMessageBase [
<category: 'radio-link'>
^ OrderedCollection new
add: self channelNumberIE;
add: self linkIdentifierIE;
yourself
]
dataRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: self l3InfoIE;
yourself
]
dataIndicationMessage [
<category: 'radio-link'>
^ self dataRequestMessage
]
errorIndicationMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrRLMCause;
instVarName: #rlm_cause; parseClass: RSLAttributeData;
beTLV; minSize: 0 maxSize: 2; yourself);
yourself
]
establishRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
]
establishConfirmMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
]
establishIndicationMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beTLV; beOptional; beLen16; yourself);
yourself
]
establishRequestMessage [
<category: 'radio-link'>
^self radioLinkMessageBase
]
releaseConfirmMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
]
releaseIndicationMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
]
releaseRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrReleaseMode;
instVarName: #release_mode; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
yourself
]
unitDataRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
minSize: 1 maxSize: 23;
beTLV; yourself);
yourself
]
unitDataIndicationMessage [
<category: 'radio-link'>
^ self unitDataRequestMessage
]
dedicatedChannelMessageBase [
<category: 'dedicated-channel'>
^ OrderedCollection new
add: self channelNumberIE;
yourself
]
channelActivationMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrActivationType;
instVarName: #activation_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrChannelMode;
instVarName: #channel_mode; parseClass: RSLAttributeData;
beTLV; minSize: 6 maxSize: 7; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrChannelIdentification;
instVarName: #channel_ident; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 6; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrEncryptionInformation;
instVarName: #encr_info; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrHandoverReference;
instVarName: #handover_ref; parseClass: RSLAttributeData;
beConditional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrBSPower;
instVarName: #bs_power; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMSPower;
instVarName: #ms_power; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrTimingAdvance;
instVarName: #timing_advance; parseClass: RSLAttributeData;
beConditional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrBSPowerParameters;
instVarName: #bs_powerparams; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMSPowerParameters;
instVarName: #ms_powerparams; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrPhysicalContext;
instVarName: #physical_context; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrSacchInformation;
instVarName: #sacch_information; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrUIC;
instVarName: #uic; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMainChannelReference;
instVarName: #main_chan_ref; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMultiRateConfiguration;
instVarName: #mr_conf; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 2; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMultiRateControl;
instVarName: #mr_control; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 2; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrSupportedCodecTypes;
instVarName: #supported_codecs; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 3; yourself);
yourself.
]
channelActivationAckMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrFrameNumber;
instVarName: #frame_number; parseClass: RSLAttributeData;
beTV; valueSize: 2; yourself);
yourself
]
channelActivationNackMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: self causeIE;
yourself
]
connectionFailureMessage [
<category: 'dedicated-channel'>
^ self channelActivationNackMessage
]
deactivateSacchMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
]
handoverDetectionMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrAccessDelay;
instVarName: #access_delay; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
modeModifyMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrChannelMode;
instVarName: #channel_mode; parseClass: RSLAttributeData;
beTLV; minSize: 6 maxSize: 7; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrEncryptionInformation;
instVarName: #encr_info; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMainChannelReference;
instVarName: #main_channel; parseClass: RSLAttributeData;
beOptional; beTV; minSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMultiRateConfiguration;
instVarName: #mr; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMultiRateControl;
instVarName: #mr_control; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrSupportedCodecTypes;
instVarName: #codec; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 3; yourself);
yourself.
]
modeModifyAck [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
]
modeModifyNack [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrCause;
instVarName: #cause; parseClass: RSLAttributeData;
beTLV; minSize: 1; yourself);
yourself
]
encryptionCommandMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrEncryptionInformation;
instVarName: #encr_info; parseClass: RSLAttributeData;
beTLV; minSize: 1; yourself);
add: self linkIdentifierIE;
add: (self l3InfoIE minSize: 4 maxSize: 4; yourself);
yourself.
]
rfChannelReleaseMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
]
rfChannelReleaseAckMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
]
commonChannelManagementBase [
<category: 'channel-management'>
^ OrderedCollection new
add: self channelNumberIE;
yourself
]
bcchInformationMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrSystemInfoType;
instVarName: #si_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrFullBcchInformation;
instVarName: #full_bcch; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 23; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrStartingTime;
instVarName: #start_time; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
pagingCommandMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrPagingGroup;
instVarName: #paging_group; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrMSIdentifty;
instVarName: #ms_identity; parseClass: RSLAttributeData;
beTLV; minSize: 1 maxSize: 9; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrChannelNeeded;
instVarName: #channel_needed; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attreMLPPPriority;
instVarName: #emlpp;
beOptional; beTV; valueSize: 2; yourself);
yourself.
]
immediateAssignCommandMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrFullImmediateAssignInfo;
instVarName: #full_info; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 23; yourself);
yourself
]
channelRequiredMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrRequestReference;
instVarName: #request_reference; parseClass: RSLAttributeData;
beTV; valueSize: 3; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrAccessDelay;
instVarName: #access_delay; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrPhysicalContext;
instVarName: #physical_context; parseClass: RSLAttributeData;
beTLV; minSize: 0; beOptional; yourself);
yourself
]
trxManagementMessageBase [
<category: 'trx-management'>
^ OrderedCollection new
]
sacchFillingMessage [
<category: 'trx-management'>
^ self trxManagementMessageBase
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrSystemInfoType;
instVarName: #si_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beOptional; beTLV; beLen16; valueSize: 20; yourself);
add: (Osmo.TLVDescription newRSLDescription
tag: RSLInformationElement attrStartingTime;
instVarName: #start_time; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
]
]
RSLInformationElement subclass: RSLAttributeData [
| data |
<category: 'RSL-OML'>
<comment: 'I am a dummy holder for a plain byte array'>
RSLAttributeData class >> readFrom: aStream with: anAttr [
| size |
size := anAttr hasLength
ifTrue: [size := self parseLength: aStream with: anAttr]
ifFalse: [anAttr valueSize].
^ self new
data: (aStream next: size);
yourself
]
RSLAttributeData class >> parseLength: aStream with: anAttr [
<category: 'parsing'>
"L3 Information has a 16bit length.. for whatever reason"
^ anAttr isLen16
ifTrue: [((aStream next: 2) asByteArray ushortAt: 1) swap16]
ifFalse: [aStream next].
]
data [
<category: 'parsing'>
^ data
]
data: aData [
<category: 'parsing'>
data := aData
]
writeOn: aMsg with: attr [
<category: 'serialize'>
"Sanity checking"
attr isFixedSize ifTrue: [
data size = attr valueSize
ifFalse: [^ self error: 'Element ', attr instVarName,
' should be of size: ', attr valueSize printString.]
].
"Write it out"
attr isLen8 ifTrue: [aMsg putByte: data size].
attr isLen16 ifTrue: [aMsg putLen16: data size].
aMsg putByteArray: data.
]
asRSLAttributeData [
<category: 'conversion'>
^ self
]
readStream [
<category: 'reading'>
^ self data readStream
]
]
RSLAttributeData subclass: RSLChannelNumber [
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 Channel Number as of 9.3.1'>
RSLChannelNumber class [
cnBmAcch [ <category: 'c-bits'> ^ 2r00001 ]
cnLmAcch [ <category: 'c-bits'> ^ 2r00010 ]
cnSdcch4Acch [ <category: 'c-bits'> ^ 2r00100 ]
cnSdcch8Acch [ <category: 'c-bits'> ^ 2r01000 ]
cnBcch [ <category: 'c-bits'> ^ 2r10000 ]
cnRach [ <category: 'c-bits'> ^ 2r10001 ]
cnPchAgch [ <category: 'c-bits'> ^ 2r10010 ]
]
RSLChannelNumber class >> ccchRach [
<category: 'creation'>
^ self new
data: #(2r10001000)
yourself.
]
cBits [
<category: 'C-bits-query'>
^ self data first bitShift: -3.
]
testCBits: bits [
| mask |
<category: 'C-bits-query'>
mask := bits.
mask highBit to: 5 do: [:each | mask := mask bitAt: each put: 1].
^ (self cBits bitAnd: mask) = bits
]
isBmAcch [
<category: 'C-bits-query'>
^ self testCBits: self class cnBmAcch.
]
isLmAcch [
<category: 'C-bits-query'>
^ self testCBits: self class cnLmAcch.
]
isSdcch4Acch [
<category: 'C-bits-query'>
^ self testCBits: self class cnSdcch4Acch.
]
isSdcch8Acch [
<category: 'C-bits-query'>
^ self testCBits: self class cnSdcch8Acch.
]
isBcch [
<category: 'C-bits-query'>
^ self testCBits: self class cnBcch.
]
isRacch [
<category: 'C-bits-query'>
^ self testCBits: self class cnRach.
]
isPchAgch [
<category: 'C-bits-query'>
^ self testCBits: self class cnPchAgch.
]
subslotNumber [
| mask high |
<category: 'subslot'>
"Sanity checking"
(self cBits bitAt: 5) = 1
ifTrue: [^self error: 'No subslots on BCCH/RACCH/PCH'].
"Now find the T-bits for the subslot"
mask := self cBits.
high := mask highBit.
1 to: high - 1 do: [:each | mask := mask bitAt: each put: 1].
high to: 5 do: [:each | mask := mask bitAt: each put: 0].
^ self cBits bitAnd: mask.
]
timeslotNumber [
<category: 'accessing'>
^ self data first bitAnd: 2r111
]
]
RSLMessageBase subclass: RSLCommonChannelManagement [
| channel_number |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 8.5 Common Channel Management Message'>
RSLCommonChannelManagement class >> messageDiscrimator [
<category: 'parsing'>
^ self discriminatorCommon.
]
RSLCommonChannelManagement class >> isTransparent [
<category: 'parsing'>
^ 0
]
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
channelNumber [
<category: 'accessing'>
^ channel_number
]
]
RSLCommonChannelManagement subclass: RSLChannelRequired [
| request_reference access_delay physical_context |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.5.3 Channel Required Message.'>
<rslMessageType: #messageTrxChannelRequired>
<rslMessageDefinition: #channelRequiredMessage>
requestReference: aRef [
<category: 'creation'>
request_reference := aRef.
]
accessDelay: aDelay [
<category: 'creation'>
access_delay := aDelay
]
]
RSLCommonChannelManagement subclass: RSLBCCHInformation [
| si_type full_bcch start_time |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.5.1 BCCH Information Message.'>
<rslMessageType: #messageTrxBcchInformation>
<rslMessageDefinition: #bcchInformationMessage>
]
RSLCommonChannelManagement subclass: RSLPagingCommand [
| paging_group ms_identity channel_needed emlpp |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.5.5'>
<rslMessageType: #messageTrxPagingCommand>
<rslMessageDefinition: #pagingCommandMessage>
pagingGroup [
<category: 'accessing'>
^ paging_group
]
msIdenity [
<category: 'accessing'>
^ OsmoGSM.GSM48MIdentity
parseFrom: ms_identity data readStream
length: ms_identity data size.
]
channelNeeded [
<category: 'accessing'>
^ channel_needed
]
emlppPriority [
<category: 'accessing'>
^ emlpp
]
]
RSLCommonChannelManagement subclass: RSLImmediateAssignment [
| full_info |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.5.6 Immediate Assign Command'>
<rslMessageType: #messageTrxImmediateAssignCommand>
<rslMessageDefinition: #immediateAssignCommandMessage>
fullL3Info [
<category: 'accessing'>
^ full_info
]
]
RSLMessageBase subclass: RSLTRXManagement [
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.6 TRX Management base'>
RSLTRXManagement class >> isTransparent [
<category: 'parsing'>
^ 0
]
RSLTRXManagement class >> messageDiscrimator [
<category: 'parsing'>
^ self discriminatorTRX
]
]
RSLTRXManagement subclass: RSLSACCHFilling [
| si_type l3_info start_time |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.6.2 SACCH Filling'>
<rslMessageType: #messageTrxSacchFilling>
<rslMessageDefinition: #sacchFillingMessage>
]
RSLMessageBase subclass: RSLDedicatedChannelManagement [
| channel_number |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.4 Dedicated Channel Management.'>
RSLDedicatedChannelManagement class >> messageDiscrimator [
<category: 'parsing'>
^ self discriminatorDedicated
]
RSLDedicatedChannelManagement class >> isTransparent [
<category: 'parsing'>
^ 0
]
channelNumber: aNr [
<category: 'creation'>
channel_number := aNr.
]
channelNumber [
<category: 'accessing'>
^ channel_number
]
]
RSLDedicatedChannelManagement subclass: RSLChannelActivation [
| activation_type channel_mode channel_ident encr_info
handover_ref bs_power ms_power timing_advance bs_powerparams
ms_powerparams physical_context sacch_information uic
main_chan_ref mr_conf mr_control supported_codecs |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.4.1 Channel Activation.'>
<rslMessageType: #messageDedChannelActication>
<rslMessageDefinition: #channelActivationMessage>
]
RSLDedicatedChannelManagement subclass: RSLChannelActivationAck [
| frame_number |
<comment: 'I represent a GSM 08.58 GSM 8.4.2 Channel Activation Ack.'>
<rslMessageType: #messageDedChannelActivationAck>
<rslMessageDefinition: #channelActivationAckMessage>
frameNumber: aNumber [
<category: 'creation'>
frame_number := aNumber
]
]
RSLDedicatedChannelManagement subclass: RSLRFChannelRelease [
<comment: 'I represent a GSM 08.58 GSM 8.4.14 RF Channel Release'>
<rslMessageType: #messageDedRfChannelRelease>
<rslMessageDefinition: #rfChannelReleaseMessage>
]
RSLDedicatedChannelManagement subclass: RSLRFChannelReleaseAck [
<comment: 'I represent a GSM 08.58 GSM 8.4.19 RF Channel Release Ack'>
<rslMessageType: #messageDedRfChannelReleaseAck>
<rslMessageDefinition: #rfChannelReleaseAckMessage>
]
RSLDedicatedChannelManagement subclass: RSLConnectionFailure [
| cause |
<comment: 'I represent a GSM 08.58 GSM 8.4.4 CONNECTION FAILURE INDICATION'>
<rslMessageType: #messageDedConnectionFailure>
<rslMessageDefinition: #connectionFailureMessage>
cause: aCause [
cause := aCause
]
]
RSLDedicatedChannelManagement subclass: RSLSacchDeactivate [
<comment: 'I represent a GSM 08.58 GSM 8.4.5 DEACTIVATE SACCH'>
<rslMessageType: #messageDedDeactivateSacch>
<rslMessageDefinition: #deactivateSacchMessage>
]
RSLDedicatedChannelManagement subclass: RSLEncryptionCommand [
| encr_info l3_info link_id |
<comment: 'I represent a GSM 08.58 GSM 8.4.6 ENCRyption CoMmaD'>
<rslMessageType: #messageDedEncryptionCommand>
<rslMessageDefinition: #encryptionCommandMessage>
l3Information [
<category: 'access'>
^ l3_info
]
linkIdentifier [
<category: 'access'>
^ link_id
]
]
RSLDedicatedChannelManagement subclass: RSLHandoverDetection [
| access_delay |
<comment: 'I represent a GSM 08.58 GSM 8.4.7 HANDOVER DETECTION'>
<rslMessageType: #messageDedHandoverDetection>
<rslMessageDefinition: #handoverDetectionMessage>
]
RSLDedicatedChannelManagement subclass: RSLModeModifyRequest [
| channel_mode encr_info main_channel mr mr_control codec |
<comment: 'I represent a GSM 08.58 8.4.9 MODE MODIFY'>
<rslMessageType: #messageDedModeModifyRequest>
<rslMessageDefinition: #modeModifyMessage>
]
RSLDedicatedChannelManagement subclass: RSLModeModifyAck [
<comment: 'I represent a GSM 08.58 8.4.10 MODE MODIFY ACKNOWLEDGE'>
<rslMessageType: #messageDedModeModifyAck>
<rslMessageDefinition: #modeModifyAck>
]
RSLDedicatedChannelManagement subclass: RSLModeModifyNack [
| cause |
<comment: 'I represent a GSM 08.58 8.4.11 MODE MODIFY NEGATIVE ACKNOWLEDGE'>
<rslMessageType: #messageDedModeModifyNack>
<rslMessageDefinition: #modeModifyNack>
]
RSLMessageBase subclass: RSLRadioLinkManagement [
| channel_number link_id |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3 Radio Linklayer messages'>
RSLRadioLinkManagement class >> isTransparent [
<category: 'parsing'>
"Let us see how far we get without having the direction. E.g everything
from the BTS is not transparent."
^ ({RSLDataRequest} includes: self)
ifTrue: [1]
ifFalse: [0].
]
RSLRadioLinkManagement class >> messageDiscrimator [
<category: 'parsing'>
^ self discriminatorRadioLink
]
channelNumber: aNr [
<category: 'creation'>
channel_number := aNr
]
linkIdentifier: aLinkId [
<category: 'creation'>
link_id := aLinkId
]
channelNumber [
<category: 'query'>
^ channel_number
]
linkIdentifier [
<category: 'query'>
^ link_id
]
]
RSLRadioLinkManagement subclass: RSLDataIndication [
| l3_info |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.2 Data indication'>
<rslMessageType: #messageRadioLinkDataIndication>
<rslMessageDefinition: #dataIndicationMessage>
l3Information: aL3Info [
<category: 'creation'>
l3_info := aL3Info
]
]
RSLRadioLinkManagement subclass: RSLEstablishIndication [
| l3_info |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.6 Establish indication'>
<rslMessageType: #messageRadioLinkEstablishIndication>
<rslMessageDefinition: #establishIndicationMessage>
l3Information: anInfo [
<category: 'parsing'>
l3_info := anInfo
]
]
RSLRadioLinkManagement subclass: RSLErrorIndication [
| rlm_cause |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.3 Establish Indication'>
<rslMessageType: #messageRadioLinkErrorIndication>
<rslMessageDefinition: #errorIndicationMessage>
RSLErrorIndication class >> isTransparent [
^1
]
rlmCause: aCause [
rlm_cause := aCause
]
]
RSLRadioLinkManagement subclass: RSLEstablishRequest [
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.4 Establish Request'>
<rslMessageType: #messageRadioLinkEstablishRequest>
<rslMessageDefinition: #establishRequestMessage>
]
RSLRadioLinkManagement subclass: RSLReleaseRequest [
| release_mode |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.7 Release Request'>
<rslMessageType: #messageRadioLinkReleaseRequest>
<rslMessageDefinition: #releaseRequestMessage>
]
RSLRadioLinkManagement subclass: RSLReleaseConfirm [
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.8 Release Confirm'>
<rslMessageType: #messageRadioLinkReleaseConfirm>
<rslMessageDefinition: #releaseConfirmMessage>
]
RSLRadioLinkManagement subclass: RSLDataRequest [
| l3_info |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.3.1 Data Request'>
<rslMessageType: #messageRadioLinkDataRequest>
<rslMessageDefinition: #dataRequestMessage>
l3Information [
<category: 'access'>
^ l3_info
]
]
RSLRadioLinkManagement subclass: RSLReleaseIndication [
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 8.3.9 Data Request'>
<rslMessageType: #messageRadioLinkReleaseIndication>
<rslMessageDefinition: #releaseIndicationMessage>
]
RSLMessageDefinitions subclass: RSLIPAMessageDefinitions [
RSLIPAMessageDefinitions class [
connectionIdentifierIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF8; instVarName: #conn_id; parseClass: RSLAttributeData;
beTV; valueSize: 2; yourself
]
localIPIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF5; instVarName: #local_ip; parseClass: RSLAttributeData;
beTV; valueSize: 4; yourself
]
localPortIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF3; instVarName: #local_port; parseClass: RSLAttributeData;
beTV; valueSize: 2; yourself
]
remoteIPIE [
^ self localIPIE
tag: 16rF0; instVarName: #remote_ip; yourself
]
remotePortIE [
^ self localPortIE
tag: 16rF1; instVarName: #remote_port; yourself.
]
speechModeIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF4; instVarName: #speech_mode; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself
]
rtpPayloadTypeIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF2; instVarName: #rtp_payload; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself
]
connectionStatisticsIE [
^ Osmo.TLVDescription newRSLDescription
tag: 16rF6; instVarName: #stats; parseClass: RSLAttributeData;
beTLV; valueSize: 28; yourself
]
createConnectionMessage [
^ OrderedCollection new
add: self channelNumberIE;
add: self speechModeIE;
add: self rtpPayloadTypeIE;
yourself
]
createConnectionAckMessage [
^ OrderedCollection new
add: self channelNumberIE;
add: self connectionIdentifierIE;
add: self localPortIE;
add: self localIPIE;
yourself
]
modifyConnectionMessage [
<category: 'ipa'>
^ OrderedCollection new
add: self channelNumberIE;
add: self connectionIdentifierIE;
add: self remoteIPIE;
add: self remotePortIE;
add: self speechModeIE;
add: self rtpPayloadTypeIE;
yourself
]
modifyConnectionAckMessage [
^ OrderedCollection new
add: self channelNumberIE;
add: self connectionIdentifierIE;
yourself
]
deleteConnectionIndMessage [
^ OrderedCollection new
add: self channelNumberIE;
add: self connectionIdentifierIE;
add: self connectionStatisticsIE;
add: self causeIE;
yourself
]
]
]
RSLMessageBase subclass: RSLIPAVendorManagement [
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a ip.access vendor extension'>
RSLIPAVendorManagement class [
messageCRCX [ <category: 'tag'> ^ 16r70 ]
messageCRCXAck [ <category: 'tag'> ^ 16r71 ]
messageCRCXNack [ <category: 'tag'> ^ 16r72 ]
messageMDCX [ <category: 'tag'> ^ 16r73 ]
messageMDCXAck [ <category: 'tag'> ^ 16r74 ]
messageMDCXNack [ <category: 'tag'> ^ 16r75 ]
messageDLCXInd [ <category: 'tag'> ^ 16r76 ]
messageDLCX [ <category: 'tag'> ^ 16r77 ]
messageDLCXAck [ <category: 'tag'> ^ 16r78 ]
messageDLCXNack [ <category: 'tag'> ^ 16r79 ]
]
RSLIPAVendorManagement class >> messageDiscrimator [
<category: 'parsing'>
^ 63
]
RSLIPAVendorManagement class >> isTransparent [
^ 0
]
RSLIPAVendorManagement class >> tlvDescription [
<category: 'tlv'>
^ RSLIPAMessageDefinitions perform: messageDefinition
]
]
RSLIPAVendorManagement subclass: RSLIPACreateConnection [
| channel_number speech_mode rtp_payload |
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a Create Connection (CRCX) message'>
<rslMessageType: #messageCRCX>
<rslMessageDefinition: #createConnectionMessage>
channelNumber [
^ channel_number
]
]
RSLIPAVendorManagement subclass: RSLIPACreateConnectionAck [
| channel_number conn_id local_port local_ip |
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a Create Connection (CRCX) ACK message'>
<rslMessageType: #messageCRCXAck>
<rslMessageDefinition: #createConnectionAckMessage>
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
localPort: aPort [
local_port := aPort
]
localIP: anAddr [
local_ip := anAddr
]
]
RSLIPAVendorManagement subclass: RSLIPAModifyConnection [
| channel_number conn_id remote_ip remote_port speech_mode rtp_payload |
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a Modify Connection (MDCX) message'>
<rslMessageType: #messageMDCX>
<rslMessageDefinition: #modifyConnectionMessage>
channelNumber [
^ channel_number
]
]
RSLIPAVendorManagement subclass: RSLIPAModifyConnectionAck [
| channel_number conn_id |
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a Modify Connection (MDCX) ACK message'>
<rslMessageType: #messageMDCXAck>
<rslMessageDefinition: #modifyConnectionAckMessage>
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
]
RSLIPAVendorManagement subclass: RSLIPADeleteConnectionInd [
| channel_number conn_id stats cause |
<category: 'BTS-RSL-IPA'>
<comment: 'I represent a Delete Connection (DLCX) Indication message'>
<rslMessageType: #messageDLCXInd>
<rslMessageDefinition: #deleteConnectionIndMessage>
defaultValues [
stats := (ByteArray new: 28) asRSLAttributeData.
cause := (ByteArray new: 1) asRSLAttributeData.
]
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
]