1
0
Fork 0

RSL: Be able to parse the SACCH filling with a 16bit length in L3 Info

Parse the SACCH filling, the first TRX management message. Introduce
the possibility to parse and write a 16bit length.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-20 13:00:48 +02:00
parent 129cd25fc5
commit f5bd0e668d
3 changed files with 101 additions and 18 deletions

View File

@ -113,7 +113,9 @@ TLVParserBase subclass: RSLMessageBase [
(each canHandle: discrim transparent: transp type: type) ifTrue: [
| res |
res := each readFrom: aStream.
aStream atEnd ifFalse: [^self error: 'Message was not fully parsed.'].
aStream atEnd ifFalse: [
aStream upToEnd printNl.
^self error: 'Message was not fully parsed.'].
^ res.
].
].
@ -126,7 +128,7 @@ TLVParserBase subclass: RSLMessageBase [
<category: 'parsing'>
"Ignore the common base classes."
({RSLCommonChannelManagement. } includes: self)
({RSLCommonChannelManagement. RSLTRXManagement.} includes: self)
ifTrue: [^false].
"Check if discriminator, transparency (asnumber) and messageType match"
@ -499,6 +501,29 @@ Object subclass: RSLMessageDefinitions [
beTLV; minSize: 0; beOptional; yourself);
yourself
]
trxManagementMessageBase [
<category: 'trx-management'>
^ OrderedCollection new
]
sacchFillingMessage [
<category: 'trx-management'>
^ self trxManagementMessageBase
add: (TLVDescription new
tag: RSLInformationElement attrSystemInfoType;
instVarName: #si_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beOptional; beTLV; beLen16; valueSize: 20; yourself);
add: (TLVDescription new
tag: RSLInformationElement attrStartingTime;
instVarName: #start_time; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
]
]
@ -508,24 +533,22 @@ RSLInformationElement subclass: RSLAttributeData [
<comment: 'I am a dummy holder for a plain byte array'>
RSLAttributeData class >> readFrom: aStream with: anAttr [
anAttr hasLength
ifTrue: [^self readFrom: aStream].
| size |
size := anAttr hasLength
ifTrue: [size := self parseLength: aStream with: anAttr]
ifFalse: [anAttr valueSize].
^ self new
data: (aStream next: anAttr valueSize);
data: (aStream next: size);
yourself
]
RSLAttributeData class >> parseLength: aStream [
RSLAttributeData class >> parseLength: aStream with: anAttr [
<category: 'parsing'>
^ aStream next
]
RSLAttributeData class >> readFrom: aStream [
<category: 'parsing'>
^ RSLAttributeData new
data: (aStream next: (self parseLength: aStream));
yourself
"L3 Information has a 16bit length.. for whatever reason"
^ anAttr isLen16
ifTrue: [((aStream next: 2) asByteArray ushortAt: 1) swap16]
ifFalse: [aStream next].
]
data [
@ -547,8 +570,8 @@ RSLInformationElement subclass: RSLAttributeData [
]
writeOn: aMsg with: attr [
attr hasLength
ifTrue: [aMsg putByte: data size].
attr isLen8 ifTrue: [aMsg putByte: data size].
attr isLen16 ifTrue: [aMsg putLen16: data size].
aMsg putByteArray: data.
]
@ -601,3 +624,34 @@ RSLCommonChannelManagement subclass: RSLBCCHInformation [
^ RSLMessageDefinitions bcchInformation
]
]
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'>
RSLSACCHFilling class >> messageType [
<category: 'parsing'>
^ self messageTrxSacchFilling
]
RSLSACCHFilling class >> tlvDescription [
<category: 'parsing'>
^ RSLMessageDefinitions sacchFillingMessage
]
]

View File

@ -17,7 +17,7 @@
"
Object subclass: TLVDescription [
| tag kind parse_class type inst_var min_size max_size |
| tag kind parse_class type inst_var min_size max_size len_size |
<category: 'BTS-TLV'>
<comment: 'I am another attempt to express optional and mandatory fields.'>
@ -70,7 +70,8 @@ Object subclass: TLVDescription [
initialize [
<category: 'creation'>
kind := self class mandatory.
type := self class tagLengthValue
type := self class tagLengthValue.
len_size := 1.
]
tag: aTag [
@ -125,6 +126,16 @@ Object subclass: TLVDescription [
^ type = self class tagLengthValue
]
isLen16 [
<category: 'access'>
^ self hasLength and: [len_size = 2]
]
isLen8 [
<category: 'access'>
^ self hasLength and: [len_size = 1]
]
presenceKind: aKind [
<category: 'creation'>
"Is this required, optional, variable?"
@ -151,6 +162,11 @@ Object subclass: TLVDescription [
self typeKind: self class tagLengthValue
]
beLen16 [
<category: 'creation'>
len_size := 2.
]
typeKind: aType [
<category: 'creation'>
type := aType

View File

@ -410,7 +410,20 @@ RoundTripTestCase subclass: RSLRoundTripTest [
^ #(12 17 1 128 30 1 39 23 85 6 25 143 148 128 0 0 0 0 0 0 0 0 0 0 0 0 0 229 4 0 43)
]
testSacchFillingData1 [
^ #(16 26 30 5 11 0 19 73 6 29 143 148 128 0 0 0 0 0 0 0 0 0 0 0 0 0)
]
testSacchFillingData2 [
^ #(16 26 30 6 11 0 12 45 6 30 0 0 0 241 16 0 1 39 255)
]
testBCCHInformation [
self roundtripTestFor: #bcchInformationData class: RSLBCCHInformation
]
testSacchFillingData [
self roundtripTestFor: #testSacchFillingData1 class: RSLSACCHFilling.
self roundtripTestFor: #testSacchFillingData2 class: RSLSACCHFilling.
]
]