smalltalk
/
osmo-st-gsm
Archived
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-gsm/Messages.st

164 lines
3.2 KiB
Smalltalk
Raw Normal View History

"General IE based message handling"
Object subclass: DataIE [
| data |
<category: 'osmo-messages'>
DataIE class >> initWith: aData [
^ self new
data: aData;
yourself
]
type [
^ data at: 1
]
type: aType [
data at: 1 put: aType.
]
data [
^ data
]
data: aData [
data := aData.
]
writeOn: aMsg [
aMsg putByteArray: data.
]
]
Object subclass: IEMessage [
<category: 'osmo-messages'>
| ies type |
IEMessage class >> initWith: type [
<category: 'creation'>
^ (self new)
type: type;
yourself
]
IEMessage class >> findIE: type with: data from: IEBase [
"TODO: This needs to move some basic dispatch class"
"Find the IE that handles the type specified"
IEBase allSubclassesDo: [:each |
each elementId = type
ifTrue: [
^ each parseFrom: data.
].
].
2010-11-24 14:20:56 +00:00
^ Exception signal: 'Unsupported IE type: ', type asString.
]
IEMessage class >> decode: aByteArray with: IEBase [
| msg dat |
msg := IEMessage initWith: (aByteArray at: 1).
dat := aByteArray copyFrom: 2.
[dat isEmpty not] whileTrue: [
| type size data |
type := dat at: 1.
size := dat at: 2.
data := dat copyFrom: 1 to: 2 + size.
dat := dat copyFrom: 3 + size.
msg addIe: (self findIE: type with: data from: IEBase).
].
^ msg
]
type: aType [
<category: 'creation'>
type := aType.
]
type [
^ type
]
addIe: aIe [
<category: 'creation'>
self ies add: aIe.
]
ies [
<category: 'access'>
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 [
<category: 'creation'>
aMsg putByte: type.
self ies do: [:each | each writeOn: aMsg ]
]
]
Object subclass: BCD [
<category: 'osmo-message'>
<comment: 'Class to deal with Binary Coded Decimals'>
BCD class >> encode: aNumber [
<category: 'access'>
| 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 [
<category: 'access'>
| 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
]
]