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

sms: Work on decoding RP-DATA/RP-ACK/RP-ERROR/RP-SMMA messages

Done on the flight to iceland, comitted in the bus to the hotel. It
is a bit rushed as the battery runs low. Updated the test result as
the RP-UserData was short in the other data
This commit is contained in:
Holger Hans Peter Freyther 2014-02-09 15:35:48 +01:00
parent ce4840a077
commit 1dd46f82bb
2 changed files with 129 additions and 9 deletions

121
GSM411.st
View File

@ -156,6 +156,10 @@ GSMCpMessage subclass: GSMCpData [
add: GSM411CpUserData asTLVDescription;
yourself
]
rpMessage [
^GSMRpMessage decode: self userData data readStream.
]
]
GSMCpMessage subclass: GSMCpAck [
@ -182,30 +186,143 @@ GSMCpMessage subclass: GSMCpError [
]
]
Osmo.TLVParserBase subclass: GSMRpMessage [
Object subclass: GSMRpInformationElement [
<category: 'OsmoGSM-SMS-Message'>
GSMRpInformationElement class >> readFrom: aStream with: anAttr [
| len |
len := aStream next asInteger.
len printNl.
^self new
readFrom: (aStream next: len);
inspect;
yourself.
]
]
GSMRpInformationElement subclass: GSMRpOrigantorAddress [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpOrigantorAddress class >> asTLVDescription [
^Osmo.TLVDescription new
beLV; instVarName: #origAddress; parseClass: self;
yourself.
]
readFrom: anArray [
data := anArray
]
]
GSMRpInformationElement subclass: GSMRpDestinationAddress [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpDestinationAddress class >> asTLVDescription [
^Osmo.TLVDescription new
beLV; instVarName: #destAddress; parseClass: self;
yourself.
]
readFrom: anArray [
data := anArray
]
]
GSMRpInformationElement subclass: GSMRpUserData [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpUserData class >> asTLVDescription [
^Osmo.TLVDescription new
beTLV; instVarName: #userData; parseClass: self;
tag: 16r41; yourself.
]
readFrom: anArray [
data := anArray
]
]
Osmo.TLVParserBase subclass: GSMRpMessage [
| direction reference |
<category: 'OsmoGSM-SMS-Message'>
GSMRpMessage class >> decode: aStream [
<category: '8.2.2'>
| mti |
"GSM 04.11 has a crazy table in 8.2.2 for the Message type indicator.
The decoding depends on the direction but right now it is still unique
so we can determine direction and and message type from that number."
mti := (aStream next bitAnd: 2r111).
mti = 2r000 ifTrue: [^GSMRpData new decode: aStream direction: #msn].
mti = 2r001 ifTrue: [^GSMRpData new decode: aStream direction: #nms].
mti = 2r010 ifTrue: [^GSMRpAck new decode: aStream direction: #msn].
mti = 2r011 ifTrue: [^GSMRpAck new decode: aStream direction: #nms].
mti = 2r100 ifTrue: [^GSMRpError new decode: aStream direction: #msn].
mti = 2r101 ifTrue: [^GSMRpError new decode: aStream direction: #nms].
mti = 2r110 ifTrue: [^GSMRpSmma new decode: aStream direction: #msn].
^self error: 'Can not decode ', mti displayString.
]
decode: aStream direction: aDirection [
direction := aDirection.
reference := aStream next asInteger.
self class tlvDescription do: [:attr |
attr isMandatory ifTrue:
[self doParse: attr stream: aStream].
attr isOptional ifTrue:
[self parseOptional: attr tag: aStream peek stream: aStream].
].
]
]
GSMRpMessage subclass: GSMRpData [
| origAddress destAddress userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.1'>
"Depending on the direction the Originator address is short."
GSMRpData class >> tlvDescription [
^OrderedCollection new
add: GSMRpOrigantorAddress asTLVDescription;
add: GSMRpDestinationAddress asTLVDescription;
add: GSMRpUserData asTLVDescription;
yourself.
]
]
GSMRpMessage subclass: GSMRpSmma [
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.2'>
GSMRpSmma class >> tlvDescription [
^OrderedCollection new
]
]
GSMRpMessage subclass: GSMRpAck [
| userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.3'>
GSMRpAck class >> tlvDescription [
^OrderedCollection new
add: GSMRpUserData asTLVDescription beOptional yourself;
yourself.
]
]
GSMRpMessage subclass: GSMRpError [
| cause userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.4'>
GSMRpError class >> tlvDescription [
^OrderedCollection new
add: GSMRpCause asTLVDescription;
add: GSMRpUserData asTLVDescription beOptional;
yourself
]
]
Eval [

View File

@ -21,18 +21,21 @@ TestCase subclass: GSM411Test [
testCPData [
| inp dec |
inp := #(16r09 16r01 16r35 16r01 16r2A 16r07 16r91 16r44
16r77 16r58 16r10 16r06 16r50 16r00 16r2B 16r04
16r04 16r81 16r32 16r24 16r00 16r00 16r80 16r21
16r03 16r41 16r24 16r32 16r40 16r1F 16r41 16r26
16r03 16r94 16r7D 16r56 16rA5 16r20 16r28 16rF2
16rE9 16r2C 16r82 16r82 16rD2 16r22 16r48 16r58
16r64 16r3E 16r9D 16r47 16r10 16rF5 16r09 16rAA) asByteArray.
inp := #[
16r09 16r01 16r23 16r00 16r0C 16r00 16r07 16r91
16r36 16r19 16r08 16r00 16r10 16r50 16r17 16r01
16r0C 16r0F 16r81 16r00 16r33 16r33 16r33 16r33
16r33 16r33 16rF3 16r00 16r00 16r09 16rAA 16rBB
16rCC 16rDD 16rEE 16rFF 16r11 16r22].
dec := GSM48MSG decode: inp readStream.
self
assert: dec type = GSMCpData messageType;
assert: dec toMessage asByteArray = inp.
self
assert: dec rpMessage toMessage asByteArray = dec userData data.
]
testCPData2 [