" (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 . " Osmo.TLVParserBase subclass: SMPPBodyBase [ SMPPBodyBase class [ genericNack [ ^16r80000000 ] bindReceiver [ ^16r00000001 ] bindReceiverResp [ ^16r80000001 ] bindTransmitter [ ^16r00000002 ] bindTransmitterResp [ ^16r80000002 ] querySM [ ^16r00000003 ] querySMResp [ ^16r80000003 ] submitSM [ ^16r00000004 ] submitSMResp [ ^16r80000004 ] deliverSM [ ^16r00000005 ] deliverSMResp [ ^16r80000005 ] unbind [ ^16r00000006 ] unbindResp [ ^16r80000006 ] replaceSM [ ^16r00000007 ] replaceSMResp [ ^16r80000007 ] cancelSM [ ^16r00000008 ] cancelSMResp [ ^16r80000008 ] bindTransceiver [ ^16r00000009 ] bindTransceiverResp [ ^16r80000009 ] outbind [ ^16r0000000B ] enquireLink [ ^16r00000015 ] enquireLinkResp [ ^16r80000015 ] submitMulti [ ^16r00000021 ] submitMultiResp [ ^16r80000021 ] alertNotification [ ^16r00000102 ] dataSM [ ^16r00000103 ] dataSMResp [ ^16r80000103 ] ] SMPPBodyBase class >> readFrom: aStream for: aHeader [ 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 [ "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. ]. ] ] ]