summaryrefslogtreecommitdiffstats
path: root/codec
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-05-13 17:27:46 +0200
committerHolger Hans Peter Freyther <holger@moiji-mobile.com>2014-05-13 17:35:48 +0200
commit9f539f1c1343cc47d1bea8f750a1cf319facf42b (patch)
treec3da5650971741840bb6aeea32f573b910a8b814 /codec
parentefb09d0f74aa792dc453b379112c37b780a9ddf1 (diff)
submit: Implement parsing of the submit SM message
Not all attribute classes have all the attributes specified. The SMPPValueHolder routines for parsing/writing were not tested/executed and might contain issues. The sm_length/short_message was combined into a single attribute as it is more like a LV. The question if the >>readFrom:with: should read the length or not is something that keeps on coming up. I need to have a more sane way of handling that.
Diffstat (limited to 'codec')
-rw-r--r--codec/SMPPBodyBase.st11
-rw-r--r--codec/SMPPSubmitSM.st109
-rw-r--r--codec/attributes/SMPPAddress.st28
-rw-r--r--codec/attributes/SMPPDataCoding.st28
-rw-r--r--codec/attributes/SMPPDefaultMessageId.st28
-rw-r--r--codec/attributes/SMPPESMClass.st110
-rw-r--r--codec/attributes/SMPPPriorityFlag.st29
-rw-r--r--codec/attributes/SMPPProtocolId.st28
-rw-r--r--codec/attributes/SMPPRegisteredDelivery.st28
-rw-r--r--codec/attributes/SMPPReplaceIfPresentFlag.st38
-rw-r--r--codec/attributes/SMPPScheduleDeliveryTime.st29
-rw-r--r--codec/attributes/SMPPServiceType.st65
-rw-r--r--codec/attributes/SMPPShortMessage.st42
-rw-r--r--codec/attributes/SMPPValidityPeriod.st29
-rw-r--r--codec/attributes/SMPPValueHolder.st43
15 files changed, 643 insertions, 2 deletions
diff --git a/codec/SMPPBodyBase.st b/codec/SMPPBodyBase.st
index ea68753..ca564d1 100644
--- a/codec/SMPPBodyBase.st
+++ b/codec/SMPPBodyBase.st
@@ -175,8 +175,15 @@ sub-classes will provide the specific bodies.'>
attribute isMandatory
ifTrue: [self doParse: attribute stream: aStream].
attribute isOptional
- ifTrue: [^self error: 'Optional attributes not implemented!'].
- ]
+ ifTrue: [
+ | tag |
+ tag := aStream peek.
+ tag = attribute tag ifTrue: [
+ aStream next.
+ self doParse: attribute stream: aStream]].
+ ].
+
+ aStream atEnd ifFalse: [^self error: 'Message not consume'].
]
writeOn: aMsg [
diff --git a/codec/SMPPSubmitSM.st b/codec/SMPPSubmitSM.st
new file mode 100644
index 0000000..3b078a2
--- /dev/null
+++ b/codec/SMPPSubmitSM.st
@@ -0,0 +1,109 @@
+"
+ (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 |
+
+ 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_submit 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
+ ]
+]
diff --git a/codec/attributes/SMPPAddress.st b/codec/attributes/SMPPAddress.st
new file mode 100644
index 0000000..ee7592d
--- /dev/null
+++ b/codec/attributes/SMPPAddress.st
@@ -0,0 +1,28 @@
+"
+ (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/>.
+"
+
+SMPPOctetString subclass: SMPPAddress [
+ <comment: 'I re-present an 5.2.8 attribute. It should be a IPv4
+ address. IPv6 is not supported'>
+
+ SMPPAddress class >> tlvDescription [
+ ^super tlvDescription
+ minSize: 0 maxSize: 20;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPDataCoding.st b/codec/attributes/SMPPDataCoding.st
new file mode 100644
index 0000000..fb0d370
--- /dev/null
+++ b/codec/attributes/SMPPDataCoding.st
@@ -0,0 +1,28 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPDataCoding [
+ <comment: 'I represent a 5.2.19'>
+
+ SMPPDataCoding class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #data_coding;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPDefaultMessageId.st b/codec/attributes/SMPPDefaultMessageId.st
new file mode 100644
index 0000000..8f1cc81
--- /dev/null
+++ b/codec/attributes/SMPPDefaultMessageId.st
@@ -0,0 +1,28 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPDefaultMessageId [
+ <comment: 'I re-present 5.2.20'>
+
+ SMPPDefaultMessageId class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #sm_default_msg_id;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPESMClass.st b/codec/attributes/SMPPESMClass.st
new file mode 100644
index 0000000..f4e0326
--- /dev/null
+++ b/codec/attributes/SMPPESMClass.st
@@ -0,0 +1,110 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPESMClass [
+ <comment: 'I re-present a 5.2.12'>
+
+ SMPPESMClass class [
+ modeBitMask [
+ <category: 'ESME->SMSC'>
+ ^2r11
+ ]
+
+ modeDefault [
+ <category: 'ESME->SMSC'>
+ ^2r00
+ ]
+
+ modeDatagram [
+ <category: 'ESME->SMSC'>
+ ^2r01
+ ]
+
+ modeForward [
+ <category: 'ESME->SMSC'>
+ ^2r10
+ ]
+
+ typeBitMask [
+ <category: 'ESME->SMSC'>
+ ^2r00111100
+ ]
+
+ typeDefault [
+ <category: 'ESME or SMSC'>
+ ^2r0 bitShift: 2
+ ]
+
+ typeSMSCDeliveryReceipt [
+ <category: 'SMSC->ESME'>
+ ^2r1 bitShift: 2
+ ]
+
+ typeESMEDeliveryAck [
+ <category: 'ESME->SMSC'>
+ ^2r10 bitShift: 2
+ ]
+
+ typeESMEUserAck [
+ <category: 'ESME->SMSC'>
+ ^2r100 bitShift: 2
+ ]
+
+ typeConversationAbort [
+ <category: 'SMSC->ESME'>
+ ^2r110 bitShift: 2
+ ]
+
+ typeIntermediateDeliveryNotification [
+ <category: 'SMSC->ESME'>
+ ^2r1000 bitShift: 2
+ ]
+
+ gsmBitMask [
+ <category: 'ESME or SMSC'>
+ ^2r11000000
+ ]
+
+ gsmNoSpecific [
+ <category: 'ESME or SMSC'>
+ ^2r00000000
+ ]
+
+ gsmUDHIIndicator [
+ <category: 'ESME or SMSC'>
+ ^2r01000000
+ ]
+
+ gsmReplyPath [
+ <category: 'ESME or SMSC'>
+ ^2r10000000
+ ]
+
+ gsmUHDIAndReplyPath [
+ <category: 'ESME/SMSC'>
+ ^self gsmUDHIIndicator bitOr: self gsmReplyPath
+ ]
+ ]
+
+ SMPPESMClass class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #esm_class;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPPriorityFlag.st b/codec/attributes/SMPPPriorityFlag.st
new file mode 100644
index 0000000..217bdfc
--- /dev/null
+++ b/codec/attributes/SMPPPriorityFlag.st
@@ -0,0 +1,29 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPPriorityFlag [
+ <comment: 'I re-present 5.2.14 of SMPPv3.4. The range is 0 to 3 but
+ the meaning depends on the type of message.'>
+
+ SMPPPriorityFlag class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #priority_flag;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPProtocolId.st b/codec/attributes/SMPPProtocolId.st
new file mode 100644
index 0000000..7ebf7db
--- /dev/null
+++ b/codec/attributes/SMPPProtocolId.st
@@ -0,0 +1,28 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPProtocolId [
+ <comment: 'I re-present a 5.2.13. But it refers to other things'>
+
+ SMPPProtocolId class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #protocol_id;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPRegisteredDelivery.st b/codec/attributes/SMPPRegisteredDelivery.st
new file mode 100644
index 0000000..42be6e6
--- /dev/null
+++ b/codec/attributes/SMPPRegisteredDelivery.st
@@ -0,0 +1,28 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPRegisteredDelivery [
+ <comment: 'I re-present a 5.2.17'>
+
+ SMPPRegisteredDelivery class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #registered_delivery;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPReplaceIfPresentFlag.st b/codec/attributes/SMPPReplaceIfPresentFlag.st
new file mode 100644
index 0000000..f475719
--- /dev/null
+++ b/codec/attributes/SMPPReplaceIfPresentFlag.st
@@ -0,0 +1,38 @@
+"
+ (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/>.
+"
+
+SMPPInteger subclass: SMPPReplaceIfPresentFlag [
+ <comment: 'I re-present a 5.2.18 flag'>
+
+ SMPPReplaceIfPresentFlag class [
+ dontReplace [
+ ^0
+ ]
+
+ replace [
+ ^1
+ ]
+ ]
+
+ SMPPReplaceIfPresentFlag class >> tlvDescription [
+ ^super tlvDescription
+ valueSize: 1;
+ instVarName: #replace_if_present_flag;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPScheduleDeliveryTime.st b/codec/attributes/SMPPScheduleDeliveryTime.st
new file mode 100644
index 0000000..7d41bde
--- /dev/null
+++ b/codec/attributes/SMPPScheduleDeliveryTime.st
@@ -0,0 +1,29 @@
+"
+ (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/>.
+"
+
+SMPPOctetString subclass: SMPPScheduleDeliveryTime [
+ <comment: 'I re-present a 5.2.15 field and can be NULL'>
+
+ SMPPScheduleDeliveryTime class >> tlvDescription [
+ "Empty string or 16 characters"
+ ^super tlvDescription
+ minSize: 0 maxSize: 16;
+ instVarName: #schedule_delivery_time;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPServiceType.st b/codec/attributes/SMPPServiceType.st
new file mode 100644
index 0000000..37d03e3
--- /dev/null
+++ b/codec/attributes/SMPPServiceType.st
@@ -0,0 +1,65 @@
+"
+ (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/>.
+"
+
+SMPPOctetString subclass: SMPPServiceType [
+ <comment: 'I re-present a ServiceType as of 5.2.11'>
+
+ SMPPServiceType class [
+ typeDefault [
+ <category: 'interface'>
+ ^''
+ ]
+
+ typeCellularMessaging [
+ <category: 'interface'>
+ ^'CMT'
+ ]
+
+ typeCellularPaging [
+ <category: 'interface'>
+ ^'CPT'
+ ]
+
+ typeVoiceMailNotification [
+ <category: 'interface'>
+ ^'VMN'
+ ]
+
+ typeVoiceMailAlerting [
+ <category: 'interface'>
+ ^'VMA'
+ ]
+
+ typeWirelessApplicationProtocol [
+ <category: 'interface'>
+ ^'WAP'
+ ]
+
+ typeUSSD [
+ <category: 'interface'>
+ ^'USSD'
+ ]
+ ]
+
+ SMPPServiceType class >> tlvDescription [
+ ^super tlvDescription
+ instVarName: #service_type;
+ minSize: 0 maxSize: 5;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPShortMessage.st b/codec/attributes/SMPPShortMessage.st
new file mode 100644
index 0000000..5925ee2
--- /dev/null
+++ b/codec/attributes/SMPPShortMessage.st
@@ -0,0 +1,42 @@
+"
+ (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/>.
+"
+
+Object subclass: SMPPShortMessage [
+ <comment: 'I represent the sm_length and short_message'>
+
+ SMPPShortMessage class >> tlvDescription [
+ ^Osmo.TLVDescription new
+ beLV;
+ instVarName: #short_message;
+ minSize: 0 maxSize: 254;
+ parseClass: self;
+ yourself
+ ]
+
+ SMPPShortMessage class >> readFrom: aStream with: anAttribute [
+ | len |
+ len := aStream next.
+ ^(aStream next: len) asString
+ ]
+
+ SMPPShortMessage class >> write: aValue on: aMsg with: anAttribute [
+ aMsg
+ putByte: aValue size;
+ putByteArray: aValue asByteArray.
+ ]
+]
diff --git a/codec/attributes/SMPPValidityPeriod.st b/codec/attributes/SMPPValidityPeriod.st
new file mode 100644
index 0000000..ffbdd61
--- /dev/null
+++ b/codec/attributes/SMPPValidityPeriod.st
@@ -0,0 +1,29 @@
+"
+ (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/>.
+"
+
+SMPPOctetString subclass: SMPPValidityPeriod [
+ <comment: 'I represent a 5.2.16 validity period. I can be
+an empty string or contain 16 characters'>
+
+ SMPPValidityPeriod class >> tlvDescription [
+ ^super tlvDescription
+ minSize: 0 maxSize: 16;
+ instVarName: #validity_period;
+ yourself
+ ]
+]
diff --git a/codec/attributes/SMPPValueHolder.st b/codec/attributes/SMPPValueHolder.st
new file mode 100644
index 0000000..0c3c9de
--- /dev/null
+++ b/codec/attributes/SMPPValueHolder.st
@@ -0,0 +1,43 @@
+"
+ (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/>.
+"
+
+Object subclass: SMPPValueHolder [
+ | tag value |
+ <comment: 'I re-present a general TLV kind of structure'>
+
+ SMPPValueHolder class >> for: aString tag: aTag [
+ ^Osmo.TLVDescription new
+ instVarName: aString;
+ tag: aTag;
+ beOptional;
+ beTLV;
+ yourself
+ ]
+
+ SMPPValueHolder class >> readFrom: aStream with: anAttribute [
+ | len |
+ len := aStream next.
+ ^(aStream next: len)
+ ]
+
+ SMPPValueHolder class >> write: aValue on: aMsg with: anAttribute [
+ aMsg
+ putByte: aValue size;
+ putByteArray: aValue asByteArray.
+ ]
+]