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

write: Implement write for the attributes and the body

This will decode and re-create the message. It is the first
round-trip test.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-13 04:25:25 +02:00
parent 1e181e67e6
commit 6cec697656
4 changed files with 38 additions and 0 deletions

View File

@ -178,4 +178,22 @@ sub-classes will provide the specific bodies.'>
ifTrue: [^self error: 'Optional attributes not implemented!'].
]
]
writeOn: aMsg [
<category: 'serialize'>
"Custom write to avoid having to box String code"
"Write each element"
self class tlvDescription do: [:attr |
| val |
val := self instVarNamed: attr instVarName.
"Now write it"
val isNil ifFalse: [
attr needsTag
ifTrue: [aMsg putByte: attr tag].
attr parseClass write: val on: aMsg with: attr.
].
]
]
]

View File

@ -33,4 +33,10 @@ Object subclass: SMPPInteger [
"This is not implemented yet"
^self error: 'The base class does not support other value sizes'.
]
SMPPInteger class >> write: aValue on: aMsg with: anAttribute [
anAttribute valueSize = 1
ifTrue: [^aMsg putByte: aValue].
^self error: 'This value size is not supported yet.'
]
]

View File

@ -38,4 +38,11 @@ Object subclass: SMPPOctetString [
"anAttribute... verify the max size"
^str contents
]
SMPPOctetString class >> write: aValue on: aMsg with: anAttr [
"Todo.. verify the size constraints..."
aMsg
putByteArray: aValue asByteArray;
putByte: 0
]
]

View File

@ -45,6 +45,13 @@ TestCase subclass: SMPPMessageTest [
self assert: msg body addressRange equals: ''.
]
testRoundTrip [
| msg res |
msg := SMPPMessage readFrom: self examplePdu readStream.
res := msg toMessage asByteArray.
self assert: res equals: self examplePdu
]
testWriteMessage [
| data |
data := (SMPPMessage new