1
0
Fork 0

TLV: Move common parsing and writing routines into the TLV base

This can be used by the RSL, OML and in the future by the ISUP,
BSSAP, GSM48 code. This TLV approach appears to be nicer than the
previous ones I had.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-20 11:01:59 +02:00
parent c4f51a3275
commit b2491f15be
2 changed files with 60 additions and 47 deletions

View File

@ -966,7 +966,7 @@ OMLMessageBase subclass: FOMMessage [
]
]
Object subclass: OMLDataField [
TLVParserBase subclass: OMLDataField [
| object_class object_instance |
OMLDataField class >> canHandle: aType [
@ -1003,34 +1003,6 @@ Object subclass: OMLDataField [
ifFalse: [aStream upToEnd asByteArray printNl. oml inspect. self error: 'Not all bytes consumed.'].
]
parseMandatory: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^self error: 'Mandatory element is missing'.].
aStream skip: 1.
self doParse: attr stream: aStream.
]
parseOptional: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^false].
aStream skip: 1.
self doParse: attr stream: aStream.
]
doParse: attr stream: aStream [
<category: 'parsing'>
attr parseClass isNil
ifTrue: [^self error: 'No parse class available'].
self instVarNamed: attr instVarName
put: (attr parseClass readFrom: aStream with: attr).
^ true
]
objectClass: aClass [
<category: 'creation'>
object_class := aClass
@ -1051,7 +1023,7 @@ Object subclass: OMLDataField [
^ object_instance
]
writeOn: aMsg [
writeHeaderOn: aMsg [
<category: 'serialize'>
"Write the type"
@ -1059,23 +1031,6 @@ Object subclass: OMLDataField [
putByte: self class attributeType;
putByte: object_class;
putByteArray: object_instance toMessage asByteArray.
self class tlvDescription do: [:attr |
| val |
val := self instVarNamed: attr instVarName.
"Check if it may be nil"
(val isNil and: [attr isOptional not])
ifTrue: [^self error: 'Mandatory parameter is nil.'].
"Now write it"
val isNil ifFalse: [
aMsg
putByte: attr tag.
val writeOn: aMsg with: attr.
].
]
]
]

View File

@ -177,3 +177,61 @@ Object subclass: TLVDescription [
^ inst_var
]
]
Object subclass: TLVParserBase [
<category: 'BTS-TLV'>
<comment: 'I am the base class for TLV like parsers. I provide common
routines for parsing.'>
parseMandatory: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^self error: 'Mandatory element is missing'.].
aStream skip: 1.
self doParse: attr stream: aStream.
]
parseOptional: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^false].
aStream skip: 1.
self doParse: attr stream: aStream.
]
doParse: attr stream: aStream [
<category: 'parsing'>
attr parseClass isNil
ifTrue: [^self error: 'No parse class available'].
self instVarNamed: attr instVarName
put: (attr parseClass readFrom: aStream with: attr).
^ true
]
writeOn: aMsg [
<category: 'serialize'>
"Write the header"
self writeHeaderOn: aMsg.
"Write each element"
self class tlvDescription do: [:attr |
| val |
val := self instVarNamed: attr instVarName.
"Check if it may be nil"
(val isNil and: [attr isOptional not])
ifTrue: [^self error: 'Mandatory parameter is nil.'].
"Now write it"
val isNil ifFalse: [
aMsg
putByte: attr tag.
val writeOn: aMsg with: attr.
].
]
]
]