smalltalk
/
osmo-st-smpp
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-smpp/codec/SMPPBodyBase.st

210 lines
5.4 KiB
Smalltalk

"
(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/>.
"
Osmo.TLVParserBase subclass: SMPPBodyBase [
<category: 'SMPP-Codec'>
<comment: 'I represent a specific "BODY" of a Payload. My
sub-classes will provide the specific bodies.'>
SMPPBodyBase class [
genericNack [
<category: '5.1.2.1 SMPP Command set'>
^16r80000000
]
bindReceiver [
<category: '5.1.2.1 SMPP Command set'>
^16r00000001
]
bindReceiverResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000001
]
bindTransmitter [
<category: '5.1.2.1 SMPP Command set'>
^16r00000002
]
bindTransmitterResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000002
]
querySM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000003
]
querySMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000003
]
submitSM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000004
]
submitSMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000004
]
deliverSM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000005
]
deliverSMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000005
]
unbind [
<category: '5.1.2.1 SMPP Command set'>
^16r00000006
]
unbindResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000006
]
replaceSM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000007
]
replaceSMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000007
]
cancelSM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000008
]
cancelSMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000008
]
bindTransceiver [
<category: '5.1.2.1 SMPP Command set'>
^16r00000009
]
bindTransceiverResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000009
]
outbind [
<category: '5.1.2.1 SMPP Command set'>
^16r0000000B
]
enquireLink [
<category: '5.1.2.1 SMPP Command set'>
^16r00000015
]
enquireLinkResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000015
]
submitMulti [
<category: '5.1.2.1 SMPP Command set'>
^16r00000021
]
submitMultiResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000021
]
alertNotification [
<category: '5.1.2.1 SMPP Command set'>
^16r00000102
]
dataSM [
<category: '5.1.2.1 SMPP Command set'>
^16r00000103
]
dataSMResp [
<category: '5.1.2.1 SMPP Command set'>
^16r80000103
]
]
SMPPBodyBase class >> readFrom: aStream for: aHeader [
<category: 'parsing'>
self allSubclassesDo: [:each |
aHeader commandId = each messageType
ifTrue: [^each new readFrom: aStream]].
^self error: 'No handler for command id = %1' % {aHeader commandId displayString}.
]
readFrom: aStream [
| description tag |
description := self class tlvDescription.
description do: [:attribute |
attribute isMandatory
ifTrue: [self doParse: attribute stream: aStream].
attribute isOptional
ifTrue: [
"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: [
tag := nil.
self doParse: attribute stream: aStream]].
].
aStream atEnd ifFalse: [^self error: 'Message not consumed'].
]
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 putLen16: attr tag].
attr parseClass write: val on: aMsg with: attr.
].
]
]
]