" (C) 2010 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 . " "General IE based message handling" Object subclass: IEBase [ type [ "Go through the elementId of the class" ^ self class elementId ] writeOnDirect: aMsg [ "This should be implemented by the subclass" self subclassResponsibility ] writeOn: aMsg [ aMsg putByte: self class elementId. self writeOnDirect: aMsg. ] ] Object subclass: IEMessage [ | ies type | IEMessage class >> initWith: type [ ^ (self new) type: type; yourself ] IEMessage class >> findIE: stream from: aIEBase on: aMsg [ "TODO: This needs to move some basic dispatch class" "Find the IE that handles the type specified" | type | type := stream next. aIEBase allSubclassesDo: [:each | each elementId = type ifTrue: [ | enc size | size := each length: stream. aMsg addIe: (each parseFrom: stream). ^ 1 + size ]. ]. ^self error: 'Unsupported IE type: ', type asString. ] IEMessage class >> decode: aStream with: aIEBase [ | msg | msg := IEMessage initWith: aStream next. [aStream atEnd] whileFalse: [ self findIE: aStream from: aIEBase on: msg. ]. ^ msg ] type: aType [ type := aType. ] type [ ^ type ] addIe: aIe [ self ies add: aIe. ] ies [ ies isNil ifTrue: [ ies := OrderedCollection new. ]. ^ ies ] findIE: type ifAbsent: block [ "Find the IE with the type" self ies do: [:each | each type = type ifTrue: [ ^ each ]. ]. ^ block value. ] findIE: type ifPresent: block [ "Find the IE with the type" self ies do: [:each | each type = type ifTrue: [ ^ block value: each ]. ]. ^ nil. ] writeOn: aMsg [ aMsg putByte: type. self ies do: [:each | each writeOn: aMsg ] ] ] Object subclass: BCD [ BCD class >> encode: aNumber [ | col num | col := OrderedCollection new. num := aNumber. 1 to: 3 do: [:each | col add: num \\ 10. num := num // 10. ]. ^ col reverse asByteArray ] BCD class >> decode: aByteArray [ | num cum | num := 0. cum := 1. aByteArray size to: 1 by: -1 do: [:each | | at | num := num + ((aByteArray at: each) * cum). cum := cum * 10. ]. ^ num ] ]