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-network/core/TLV.st

303 lines
6.7 KiB
Smalltalk

"
(C) 2012-2014 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/>.
"
Object subclass: TLVDescription [
| tag kind parse_class type inst_var min_size max_size len_size force_tag |
<category: 'OsmoNetwork-TLV'>
<comment: 'I am another attempt to express optional and mandatory fields.'>
TLVDescription class [
optional [
<category: 'presence'>
^ #optional
]
mandatory [
<category: 'presence'>
^ #mandatory
]
conditional [
<category: 'presence'>
^ #conditional
]
tagLengthValue [
<category: 'type'>
^ #tlv
]
tagValue [
<category: 'type'>
^ #tv
]
valueOnly [
<category: 'type'>
^ #valueOnly
]
tagOnly [
<category: 'type'>
^ #tagOnly
]
lengthValue [
<category: 'type'>
^#lv
]
new [
<category: 'creation'>
^self basicNew initialize
]
]
initialize [
<category: 'creation'>
kind := self class mandatory.
type := self class tagLengthValue.
len_size := 1.
force_tag := false.
]
tag: aTag [
<category: 'creation'>
tag := aTag
]
tag [
<category: 'access'>
"The tag value for this tag inside the bytestream"
^ tag
]
minSize: aMin maxSize: aMax [
<category: 'size'>
"This only makes sense for *LV elements"
min_size := aMin.
max_size := aMax.
]
minSize: aMin [
min_size := aMin.
max_size := nil.
]
valueSize: aSize [
<category: 'size'>
^ self minSize: aSize maxSize: aSize.
]
valueSize [
^ max_size
]
isOptional [
<category: 'access'>
^ kind = self class optional
]
isMandatory [
<category: 'access'>
^ kind = self class mandatory
]
isConditional [
<category: 'access'>
^ kind = self class conditional
]
isFixedSize [
<category: 'access'>
^ type = self class tagValue or: [type = self class valueOnly].
]
hasLength [
<category: 'access'>
^ type = self class tagLengthValue or: [type = self class lengthValue]
]
isLen16 [
<category: 'access'>
^ self hasLength and: [len_size = 2]
]
isLen8 [
<category: 'access'>
^ self hasLength and: [len_size = 1]
]
isForcedTag [
<category: 'access'>
^ force_tag
]
hasTag [
<category: 'access'>
^type ~= self class lengthValue and: [type ~= self class valueOnly]
]
needsTag [
<category: 'access'>
^force_tag or: [self hasTag and: [self isOptional or: [self isConditional]]].
]
presenceKind: aKind [
<category: 'creation'>
"Is this required, optional, variable?"
kind := aKind
]
beOptional [
<category: 'creation'>
self presenceKind: self class optional.
]
beConditional [
<category: 'creation'>
self presenceKind: self class conditional.
]
beForceTagged [
<category: 'creation'>
"Write a tag even if this element is mandatory"
force_tag := true.
]
beTagOnly [
<category: 'creation'>
self typeKind: self class tagOnly.
]
beTV [
<category: 'creation'>
self typeKind: self class tagValue
]
beTLV [
<category: 'creation'>
self typeKind: self class tagLengthValue
]
beLV [
<category: 'creation'>
self typeKind: self class lengthValue
]
beLen16 [
<category: 'creation'>
len_size := 2.
]
typeKind: aType [
<category: 'creation'>
type := aType
]
typeKind [
<category: 'accessing'>
^ type
]
parseClass: aClass [
<category: 'creation'>
"The class to be used to parse this"
parse_class := aClass
]
parseClass [
<category: 'creation'>
^ parse_class
]
instVarName: aName [
<category: 'creation'>
inst_var := aName
]
instVarName [
<category: 'accessing'>
^ inst_var
]
]
Object subclass: TLVParserBase [
<category: 'OsmoNetwork-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 <1p> element is missing'
expandMacrosWith: attr instVarName).].
aStream skip: 1.
self doParse: attr stream: aStream.
]
parseConditional: attr tag: aTag stream: aStream [
<category: 'parsing'>
^ self parseOptional: attr tag: aTag 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 isMandatory])
ifTrue: [^self error: 'Mandatory parameter is nil.'].
"Now write it"
val isNil ifFalse: [
attr needsTag ifTrue: [aMsg putByte: attr tag].
val writeOn: aMsg with: attr.
].
]
]
]