" (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 . " Object subclass: TLVDescription [ | tag kind parse_class type inst_var min_size max_size len_size force_tag | TLVDescription class [ optional [ ^ #optional ] mandatory [ ^ #mandatory ] conditional [ ^ #conditional ] tagLengthValue [ ^ #tlv ] tagValue [ ^ #tv ] valueOnly [ ^ #valueOnly ] tagOnly [ ^ #tagOnly ] lengthValue [ ^#lv ] new [ ^self basicNew initialize ] ] initialize [ kind := self class mandatory. type := self class tagLengthValue. len_size := 1. force_tag := false. ] tag: aTag [ tag := aTag ] tag [ "The tag value for this tag inside the bytestream" ^ tag ] minSize: aMin maxSize: aMax [ "This only makes sense for *LV elements" min_size := aMin. max_size := aMax. ] minSize: aMin [ min_size := aMin. max_size := nil. ] valueSize: aSize [ ^ self minSize: aSize maxSize: aSize. ] valueSize [ ^ max_size ] isOptional [ ^ kind = self class optional ] isMandatory [ ^ kind = self class mandatory ] isConditional [ ^ kind = self class conditional ] isFixedSize [ ^ type = self class tagValue or: [type = self class valueOnly]. ] hasLength [ ^ type = self class tagLengthValue or: [type = self class lengthValue] ] isLen16 [ ^ self hasLength and: [len_size = 2] ] isLen8 [ ^ self hasLength and: [len_size = 1] ] isForcedTag [ ^ force_tag ] hasTag [ ^type ~= self class lengthValue and: [type ~= self class valueOnly] ] needsTag [ ^force_tag or: [self hasTag and: [self isOptional or: [self isConditional]]]. ] presenceKind: aKind [ "Is this required, optional, variable?" kind := aKind ] beOptional [ self presenceKind: self class optional. ] beConditional [ self presenceKind: self class conditional. ] beForceTagged [ "Write a tag even if this element is mandatory" force_tag := true. ] beTagOnly [ self typeKind: self class tagOnly. ] beTV [ self typeKind: self class tagValue ] beTLV [ self typeKind: self class tagLengthValue ] beLV [ self typeKind: self class lengthValue ] beLen16 [ len_size := 2. ] typeKind: aType [ type := aType ] typeKind [ ^ type ] parseClass: aClass [ "The class to be used to parse this" parse_class := aClass ] parseClass [ ^ parse_class ] instVarName: aName [ inst_var := aName ] instVarName [ ^ inst_var ] ] Object subclass: TLVParserBase [ parseMandatory: attr tag: aTag stream: aStream [ 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 [ ^ self parseOptional: attr tag: aTag stream: aStream ] parseOptional: attr tag: aTag stream: aStream [ aTag = attr tag ifFalse: [^false]. aStream skip: 1. self doParse: attr stream: aStream. ] doParse: attr stream: aStream [ attr parseClass isNil ifTrue: [^self error: 'No parse class available']. self instVarNamed: attr instVarName put: (attr parseClass readFrom: aStream with: attr). ^ true ] writeOn: aMsg [ "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. ]. ] ] ]