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-network/m2ua/M2UAMSG.st

148 lines
4.0 KiB
Smalltalk

"
(C) 2011-2013 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/>.
"
Object subclass: M2UAMSG [
| msg_class msg_type tags |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I can parse a M2UA message from the wire, allow you
to see the class, type and include tags. In C the structure will
look like this:
struct m2ua_common_hdr {
uint8_t version;
uint8_t spare;
uint8_t msg_class;
uint8_t msg_type;
uint32_t msg_length;
uint8_t data[0];
} __attribute__((packed));
struct m2ua_parameter_hdr {
uint16_t tag;
uint16_t len;
uint8_t data[0];
} __attribute__((packed));
'>
M2UAMSG class >> parseFrom: aMsg [
<category: 'parsing'>
self logDataContext: aMsg area: #m2ua.
^ self new
parseFrom: aMsg readStream;
yourself.
]
M2UAMSG class >> fromClass: aClass type: aType [
<category: 'parsing'>
^ self new
instVarNamed: #msg_class put: aClass;
instVarNamed: #msg_type put: aType;
yourself.
]
msgClass [
<category: 'accessing'>
^ msg_class
]
msgType [
<category: 'accessing'>
^ msg_type
]
findTag: aTag ifAbsent: aBlock [
"I find a tag with a tag identifier"
<category: 'accessing'>
self tags do: [:each |
(each isTag: aTag) ifTrue: [
^ each
]
].
^ aBlock value
]
tags [
<category: 'private'>
^ tags ifNil: [tags := OrderedCollection new]
]
parseFrom: aStream [
| version spare len end |
<category: 'parsing'>
version := aStream next.
version = M2UAConstants version ifFalse: [
self logError:
('M2UA version is wrong <1p>.' expandMacrosWith: version) area: #m2ua.
self error: ('M2UA version is wrong <1p>.' expandMacrosWith: version).
].
spare := aStream next.
spare = M2UAConstants spare ifFalse: [
self logError: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare) area: #m2ua.
self error: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare).
].
msg_class := aStream next.
msg_type := aStream next.
len := ((aStream next: 4) uintAt: 1) swap32.
aStream size - aStream position < (len - 8) ifTrue: [
self logError: ('M2UA length is not plausible <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position)
area: #m2ua.
self error: ('M2UA length is not plausible <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position).
].
tags := OrderedCollection new.
end := aStream position + len - 8.
[aStream position < end] whileTrue: [
tags add: (M2UATag fromStream: aStream)
].
]
addTag: aTag [
<category: 'encoding'>
self tags add: aTag.
]
writeOn: aMsg [
| tag_data |
<category: 'private'>
"Create the tag data"
tag_data := MessageBuffer new.
self tags do: [:each |
each writeOn: tag_data
].
aMsg putByte: M2UAConstants version.
aMsg putByte: M2UAConstants spare.
aMsg putByte: msg_class.
aMsg putByte: msg_type.
aMsg putLen32: tag_data size + 8.
aMsg putByteArray: tag_data.
]
]