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

112 lines
5.2 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: SMPPSubmitSM [
| 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 source_addr_subunit
destination_port dest_addr_subunit sar_msg_ref_num
sar_total_segments sar_segment_seqnum more_messages_to_send
payload_type message_payload privacy_indicator callback_num
callback_num_pres_ind callback_num_atag source_subaddress
dest_subaddress user_response_code display_time sms_signal
ms_validity ms_msg_wait_facilities number_of_messages
alert_on_msg_delivery language_indicator its_reply_type
its_session_info ussd_service_op |
<category: 'SMPP-Codec'>
SMPPSubmitSM class >> messageType [
^self submitSM
]
SMPPSubmitSM 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: #source_addr_subunit tag: 16r000D);
add: (SMPPValueHolder for: #destination_port tag: 16r020B);
add: (SMPPValueHolder for: #dest_addr_subunit tag: 16r0005);
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: #more_messages_to_send tag: 16r0426 );
add: (SMPPValueHolder for: #payload_type tag: 16r0019);
add: (SMPPValueHolder for: #message_payload tag: 16r0424);
add: (SMPPValueHolder for: #privacy_indicator tag: 16r0201);
add: (SMPPValueHolder for: #callback_num tag: 16r0381);
add: (SMPPValueHolder for: #callback_num_pres_ind tag: 16r0302);
add: (SMPPValueHolder for: #callback_num_atag tag: 16r0303);
add: (SMPPValueHolder for: #source_subaddress tag: 16r0202);
add: (SMPPValueHolder for: #dest_subaddress tag: 16r0203);
add: (SMPPValueHolder for: #user_response_code tag: 16r0205);
add: (SMPPValueHolder for: #display_time tag: 16r1201);
add: (SMPPValueHolder for: #sms_signal tag: 16r1203);
add: (SMPPValueHolder for: #ms_validity tag: 16r1204);
add: (SMPPValueHolder for: #ms_msg_wait_facilities tag: 16r0030);
add: (SMPPValueHolder for: #number_of_messages tag: 16r0304);
add: (SMPPValueHolder for: #alert_on_msg_delivery tag: 16r130C);
add: (SMPPValueHolder for: #language_indicator tag: 16r020D);
add: (SMPPValueHolder for: #its_reply_type tag: 16r1380);
add: (SMPPValueHolder for: #its_session_info tag: 16r1383);
add: (SMPPValueHolder for: #ussd_service_op tag: 16r0501);
yourself
]
sourceAddress [
<category: 'accessing'>
^source_addr
]
destinationAddress [
<category: 'accessing'>
^destination_addr
]
shortMessage [
<category: 'accessing'>
^short_message
]
]