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

170 lines
3.8 KiB
Smalltalk

"
(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 <http://www.gnu.org/licenses/>.
"
"General IE based message handling"
Object subclass: IEBase [
<category: 'OsmoGSM'>
<comment: 'I am a base for IE types'>
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 |
<category: 'OsmoGSM'>
IEMessage class >> initWith: type [
<category: 'creation'>
^ (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 [
<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: 'OsmoGSM'>
<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
]
]