aboutsummaryrefslogtreecommitdiffstats
path: root/Messages.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-11-22 17:11:08 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-11-22 17:13:53 +0100
commitc28b116689b03dcbd426e8028914bd3b6fa7b878 (patch)
tree27109befcedbaa5258bf5a6ecc556caf4fd21b40 /Messages.st
parent5ed751c24e22c5c5712824240ff46f749074f7b3 (diff)
Decode: Work on decoding the messages...
This is a lot of work in progress to recursively decode the messages.
Diffstat (limited to 'Messages.st')
-rw-r--r--Messages.st73
1 files changed, 73 insertions, 0 deletions
diff --git a/Messages.st b/Messages.st
index 6976296..bc8c908 100644
--- a/Messages.st
+++ b/Messages.st
@@ -1,4 +1,38 @@
"General IE based message handling"
+Object subclass: DataIE [
+ | type data |
+
+ <category: 'osmo-messages'>
+ DataIE class >> initWith: aType data: aData [
+ ^ self new
+ type: aType;
+ data: aData;
+ yourself
+ ]
+
+ type [
+ ^ type
+ ]
+
+ type: aType [
+ type := aType.
+ ]
+
+ data [
+ ^ data
+ ]
+
+ data: aData [
+ data := aData.
+ ]
+
+ writeOn: aMsg [
+ aMsg putByte: type.
+ aMsg putByte: data size.
+ aMsg putByteArray: data.
+ ]
+]
+
Object subclass: IEMessage [
<category: 'osmo-messages'>
| ies type |
@@ -10,11 +44,50 @@ Object subclass: IEMessage [
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"
+
+ ^ DataIE initWith: type data: data.
+"
+ IEBase allSubclassesDo: [:each |
+ each elementId = type
+ ifTrue: [
+ ^ each parseFrom: data.
+ ].
+ ].
+
+ ^ Exception signal: 'Unsupported IE type: ', type.
+"
+ ]
+
+ 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: 3 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.