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/SMPPDeliverSM.st

175 lines
5.7 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/>.
"
SMPPBodyBase subclass: SMPPDeliverSM [
| service_type source_addr_ton source_addr_npi source_addr
dest_addr_ton dest_addr_npi destination_addr esm_class
protocol_id priority_flag schedule_delivery_time
validity_period registered_delivery replace_if_present_flag
data_coding sm_default_msg_id short_message
user_message_reference source_port destination_port
sar_msg_ref_num sar_total_segments sar_segment_seqnum
user_response_code privacy_indicator payload_type
message_payload callback_num source_subaddress
dest_subaddress language_indicator its_session_info
network_error_code message_state receipted_message_id |
<category: 'SMPP-Codec'>
SMPPDeliverSM class >> messageType [
^self deliverSM
]
SMPPDeliverSM class >> tlvDescription [
^OrderedCollection new
add: SMPPServiceType tlvDescription;
add: (SMPPAddressTypeOfNumber tlvDescription
instVarName: #source_addr_ton; yourself);
add: (SMPPAddressNumberingPlanIndicator tlvDescription
instVarName: #source_addr_npi; yourself);
add: (SMPPAddress tlvDescription
instVarName: #source_addr; yourself);
add: (SMPPAddressTypeOfNumber tlvDescription
instVarName: #dest_addr_ton; yourself);
add: (SMPPAddressNumberingPlanIndicator tlvDescription
instVarName: #dest_addr_npi; yourself);
add: (SMPPAddress tlvDescription
instVarName: #destination_addr; yourself);
add: SMPPESMClass tlvDescription;
add: SMPPProtocolId tlvDescription;
add: SMPPPriorityFlag tlvDescription;
add: SMPPScheduleDeliveryTime tlvDescription;
add: SMPPValidityPeriod tlvDescription;
add: SMPPRegisteredDelivery tlvDescription;
add: SMPPReplaceIfPresentFlag tlvDescription;
add: SMPPDataCoding tlvDescription;
add: SMPPDefaultMessageId tlvDescription;
add: SMPPShortMessage tlvDescription;
add: (SMPPValueHolder for: #user_message_reference tag: 16r0204);
add: (SMPPValueHolder for: #source_port tag: 16r020A);
add: (SMPPValueHolder for: #destination_port tag: 16r020B);
add: (SMPPValueHolder for: #sar_msg_ref_num tag: 16r020C);
add: (SMPPValueHolder for: #sar_total_segments tag: 16r020E);
add: (SMPPValueHolder for: #sar_segment_seqnum tag: 16r020F);
add: (SMPPValueHolder for: #user_response_code tag: 16r0205);
add: (SMPPValueHolder for: #privacy_indicator tag: 16r0201);
add: (SMPPValueHolder for: #payload_type tag: 16r0019);
add: (SMPPValueHolder for: #message_payload tag: 16r0424);
add: (SMPPValueHolder for: #callback_num tag: 16r0381);
add: (SMPPValueHolder for: #source_subaddress tag: 16r0202);
add: (SMPPValueHolder for: #dest_subaddress tag: 16r0203);
add: (SMPPValueHolder for: #language_indicator tag: 16r020D);
add: (SMPPValueHolder for: #its_session_info tag: 16r1383);
add: (SMPPValueHolder for: #network_error_code tag: 16r0423);
add: (SMPPValueHolder for: #message_state tag: 16r0427);
add: (SMPPValueHolder for: #receipted_message_id tag: 16r001E);
yourself
]
sourceAddress [
<category: 'accessing'>
^source_addr
]
destinationAddress [
<category: 'accessing'>
^destination_addr
]
shortMessage [
<category: 'accessing'>
^short_message
]
destinationAddress: aString [
destination_addr := aString
]
scheduleDeliveryTime: aString [
schedule_delivery_time := aString
]
registeredDelivery: anInteger [
registered_delivery := anInteger
]
dontReplaceIfPresent [
replace_if_present_flag := 0
]
destinationNumberingPlanIndicator: anInteger [
dest_addr_npi := anInteger
]
destinationTypeOfNumber: anInteger [
dest_addr_ton := anInteger
]
dataCoding: anInteger [
data_coding := 0
]
sourceAddress: aString [
source_addr := aString
]
protocolId: anInteger [
protocol_id := anInteger
]
esmClass: anInteger [
esm_class := anInteger
]
priorityLevel: anInteger [
priority_flag := 0
]
shortMessage: aCollection [
short_message := aCollection
]
messagePayload: aCollection [
message_payload := aCollection
]
sourceNumberingPlanIndicator: anInteger [
source_addr_npi := anInteger
]
defaultMessageID: anInteger [
sm_default_msg_id := 0
]
serviceType: anInteger [
service_type := anInteger
]
sourceTypeOfNumber: anInteger [
source_addr_ton := anInteger
]
registeredValidity: anInteger [
self shouldBeImplemented
]
validityPeriod: aString [
validity_period := aString
]
]