smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0

Decode: Work on decoding the messages...

This is a lot of work in progress to recursively decode
the messages.
This commit is contained in:
Holger Hans Peter Freyther 2010-11-22 17:11:08 +01:00
parent 5ed751c24e
commit c28b116689
3 changed files with 126 additions and 6 deletions

View File

@ -28,24 +28,53 @@ Object subclass: BSSAPHelper [
]
]
Object subclass: BSSAPManagement [
| payload |
Object subclass: BSSAPMessage [
BSSAPMessage class >> decode: bssap [
| type |
type := bssap at: 1.
BSSAPMessage allSubclassesDo: [:each |
each msgType = type
ifTrue: [
^ each parseFrom: bssap.
]
].
^ Error signal: 'No handler for: ', type asString.
]
]
BSSAPMessage subclass: BSSAPManagement [
| data |
BSSAPManagement class >> msgType [ <category: 'factory'> ^ BSSAPHelper msgManagemnt ]
BSSAPManagement class >> initWith: data [
^ (self new)
payload: data;
data: data;
yourself.
]
payload: aPayload [
payload := aPayload.
BSSAPMessage class >> parseFrom: aByteArray [
| size data |
size := aByteArray at: 2.
data := aByteArray copyFrom: 3 to: 2 + size.
^ BSSAPManagement initWith: data.
]
data: aPayload [
data := aPayload.
]
data [
^ data
]
writeOn: aMsg [
| dat |
aMsg putByte: BSSAPHelper msgManagemnt.
dat := payload toMessageOrByteArray.
dat := data toMessageOrByteArray.
aMsg putByte: dat size.
aMsg putByteArray: dat.
]

View File

@ -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.

View File

@ -44,6 +44,16 @@ TestCase subclass: GSM0808Test [
16r75 16r30 16r17 16r03 16r01 16r02 16r03) asByteArray.
self assert: buf asByteArray = res
]
testIEDecoding [
| inp res |
inp := #(16r57 16r05 16r08 16r00 16r72 16rF4 16r80 16r20 16r12
16r75 16r30 16r17 16r03 16r01 16r02 16r03) asByteArray.
res := IEMessage decode: inp with: GSM0808IE.
self assert: res type = GSM0808Helper msgComplL3.
self assert: res ies size = 2.
]
]
TestCase subclass: BSSAPTest [
@ -63,6 +73,14 @@ TestCase subclass: BSSAPTest [
self assert: man toMessage asByteArray = #(0 3 1 2 3) asByteArray.
]
testParseManagement [
| man |
man := BSSAPMessage decode: #(0 3 1 2 3) asByteArray.
self assert: (man isKindOf: BSSAPManagement).
self assert: man data = #(1 2 3) asByteArray.
]
testPrependDTAP [
| msg |
msg := Osmo.MessageBuffer new.