1
0
Fork 0

tlv: Only write a tag if it was forced or the type is optional

This commit is contained in:
Holger Hans Peter Freyther 2014-02-09 22:04:04 +01:00
parent 564087a32d
commit abbad4a7af
2 changed files with 27 additions and 5 deletions

View File

@ -132,7 +132,7 @@ Object subclass: TLVDescription [
hasLength [
<category: 'access'>
^ type = self class tagLengthValue
^ type = self class tagLengthValue or: [type = self class lengthValue]
]
isLen16 [
@ -150,6 +150,16 @@ Object subclass: TLVDescription [
^ 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]].
]
presenceKind: aKind [
<category: 'creation'>
"Is this required, optional, variable?"
@ -286,8 +296,7 @@ Object subclass: TLVParserBase [
"Now write it"
val isNil ifFalse: [
aMsg
putByte: attr tag.
attr needsTag ifTrue: [aMsg putByte: attr tag].
val writeOn: aMsg with: attr.
].
]

View File

@ -42,8 +42,21 @@ TestCase subclass: TLVDescriptionTest [
self assert: tlv tag = 16r23.
tlv beLV.
self assert: tlv typeKind = #lv.
self
assert: tlv typeKind equals: #lv;
assert: tlv hasLength;
deny: tlv hasTag.
tlv beTLV.
self assert: tlv typeKind = #tlv.
self
assert: tlv typeKind equals: #tlv;
assert: tlv hasLength;
assert: tlv hasTag.
tlv beTagOnly.
self
assert: tlv typeKind equals: #tagOnly;
assert: tlv hasTag;
deny: tlv hasLength.
]
]