summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-06-17 19:21:34 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-06-17 19:21:34 +0200
commitde471382a40d2ec8201fec11f37490a32e1267a1 (patch)
treeece6979a6085f49e995747a3f4803596a1dcf5b7
parent2008f19ac190ae317924283d9e88b79b9e0c8e85 (diff)
codec: Implement parsing trx bind resp and fix optional parsing
-rw-r--r--codec/SMPPBindTransceiverResponse.st41
-rw-r--r--codec/SMPPBodyBase.st13
-rw-r--r--codec/attributes/SMPPValueHolder.st5
-rw-r--r--package.xml1
-rw-r--r--test/SMPPMessageTest.st18
5 files changed, 71 insertions, 7 deletions
diff --git a/codec/SMPPBindTransceiverResponse.st b/codec/SMPPBindTransceiverResponse.st
new file mode 100644
index 0000000..922db99
--- /dev/null
+++ b/codec/SMPPBindTransceiverResponse.st
@@ -0,0 +1,41 @@
+"
+ (C) 2014 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/>.
+"
+
+SMPPBodyBase subclass: SMPPBindTransceiverResponse [
+ | system_id sc_interface_version |
+
+ <category: 'SMPP-Codec'>
+ <comment: 'I represent a response and there should be a intermediate
+ class just like with the SMPPBindTransmitter'>
+
+ SMPPBindTransceiverResponse class >> messageType [
+ ^self bindTransceiverResp
+ ]
+
+ SMPPBindTransceiverResponse class >> tlvDescription [
+ ^OrderedCollection new
+ add: SMPPSystemId tlvDescription;
+ add: (SMPPValueHolder for: #sc_interface_version tag: 16r0210);
+ yourself
+ ]
+
+ systemId [
+ ^system_id
+ ]
+]
+
diff --git a/codec/SMPPBodyBase.st b/codec/SMPPBodyBase.st
index 99c0da8..7dd1f50 100644
--- a/codec/SMPPBodyBase.st
+++ b/codec/SMPPBodyBase.st
@@ -168,17 +168,20 @@ sub-classes will provide the specific bodies.'>
]
readFrom: aStream [
- | description |
+ | description tag |
description := self class tlvDescription.
description do: [:attribute |
attribute isMandatory
ifTrue: [self doParse: attribute stream: aStream].
attribute isOptional
ifTrue: [
- | tag |
- tag := aStream peek.
+ "Read the tag if we have not done so far. We can not
+ peek for more than one character."
+ (tag isNil and: [aStream atEnd not]) ifTrue:
+ [tag := ((aStream next: 2) shortAt: 1) swap16].
+
tag = attribute tag ifTrue: [
- aStream next.
+ tag := nil.
self doParse: attribute stream: aStream]].
].
@@ -197,7 +200,7 @@ sub-classes will provide the specific bodies.'>
"Now write it"
val isNil ifFalse: [
attr needsTag
- ifTrue: [aMsg putByte: attr tag].
+ ifTrue: [aMsg putLen16: attr tag].
attr parseClass write: val on: aMsg with: attr.
].
]
diff --git a/codec/attributes/SMPPValueHolder.st b/codec/attributes/SMPPValueHolder.st
index 0c3c9de..127ab58 100644
--- a/codec/attributes/SMPPValueHolder.st
+++ b/codec/attributes/SMPPValueHolder.st
@@ -23,6 +23,7 @@ Object subclass: SMPPValueHolder [
SMPPValueHolder class >> for: aString tag: aTag [
^Osmo.TLVDescription new
instVarName: aString;
+ parseClass: self;
tag: aTag;
beOptional;
beTLV;
@@ -31,13 +32,13 @@ Object subclass: SMPPValueHolder [
SMPPValueHolder class >> readFrom: aStream with: anAttribute [
| len |
- len := aStream next.
+ len := ((aStream next: 2) shortAt: 1) swap16.
^(aStream next: len)
]
SMPPValueHolder class >> write: aValue on: aMsg with: anAttribute [
aMsg
- putByte: aValue size;
+ putLen16: aValue size;
putByteArray: aValue asByteArray.
]
]
diff --git a/package.xml b/package.xml
index 0e6b51d..2707842 100644
--- a/package.xml
+++ b/package.xml
@@ -8,6 +8,7 @@
<filein>codec/SMPPBodyBase.st</filein>
<filein>codec/SMPPBindTransmitterBody.st</filein>
<filein>codec/SMPPBindTransceiver.st</filein>
+ <filein>codec/SMPPBindTransceiverResponse.st</filein>
<filein>codec/SMPPEnquireLink.st</filein>
<filein>codec/SMPPGenericNack.st</filein>
<filein>codec/SMPPUnbind.st</filein>
diff --git a/test/SMPPMessageTest.st b/test/SMPPMessageTest.st
index f459540..6d40fc2 100644
--- a/test/SMPPMessageTest.st
+++ b/test/SMPPMessageTest.st
@@ -68,6 +68,13 @@ TestCase subclass: SMPPMessageTest [
16r32]
]
+ exampleBindResponse [
+ ^#[16r00 16r00 16r00 16r1D 16r80 16r00 16r00 16r09
+ 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00
+ 16r53 16r4D 16r50 16r50 16r4D 16r41 16r50 16r00
+ 16r02 16r10 16r00 16r01 16r34]
+ ]
+
testReadMessage [
| msg |
msg := SMPPMessage readFrom: self examplePdu readStream.
@@ -141,4 +148,15 @@ TestCase subclass: SMPPMessageTest [
res := msg toMessage asByteArray.
self assert: res equals: self exampleSubmitSM.
]
+
+ testBindResponse [
+ | msg res |
+ msg := SMPPMessage readFrom: self exampleBindResponse readStream.
+ self assert: msg body class equals: SMPPBindTransceiverResponse.
+ self assert: msg body systemId equals: 'SMPPMAP'.
+
+ "Do round trip test"
+ res := msg toMessage asByteArray.
+ self assert: res equals: self exampleBindResponse.
+ ]
]