smalltalk
/
osmo-st-smpp
Archived
1
0
Fork 0

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.
This commit is contained in:
Holger Hans Peter Freyther 2014-05-13 17:27:46 +02:00
parent efb09d0f74
commit 9f539f1c13
17 changed files with 682 additions and 2 deletions

View File

@ -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 [

109
codec/SMPPSubmitSM.st Normal file
View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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
]
]

View File

@ -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.
]
]

View File

@ -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
]
]

View File

@ -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.
]
]

View File

@ -11,6 +11,7 @@
<filein>codec/SMPPEnquireLink.st</filein>
<filein>codec/SMPPGenericNack.st</filein>
<filein>codec/SMPPUnbind.st</filein>
<filein>codec/SMPPSubmitSM.st</filein>
<filein>codec/attributes/SMPPOctetString.st</filein>
<filein>codec/attributes/SMPPInteger.st</filein>
@ -21,6 +22,19 @@
<filein>codec/attributes/SMPPAddressTypeOfNumber.st</filein>
<filein>codec/attributes/SMPPAddressNumberingPlanIndicator.st</filein>
<filein>codec/attributes/SMPPAddressRange.st</filein>
<filein>codec/attributes/SMPPServiceType.st</filein>
<filein>codec/attributes/SMPPAddress.st</filein>
<filein>codec/attributes/SMPPESMClass.st</filein>
<filein>codec/attributes/SMPPProtocolId.st</filein>
<filein>codec/attributes/SMPPPriorityFlag.st</filein>
<filein>codec/attributes/SMPPScheduleDeliveryTime.st</filein>
<filein>codec/attributes/SMPPValidityPeriod.st</filein>
<filein>codec/attributes/SMPPRegisteredDelivery.st</filein>
<filein>codec/attributes/SMPPReplaceIfPresentFlag.st</filein>
<filein>codec/attributes/SMPPDataCoding.st</filein>
<filein>codec/attributes/SMPPDefaultMessageId.st</filein>
<filein>codec/attributes/SMPPValueHolder.st</filein>
<filein>codec/attributes/SMPPShortMessage.st</filein>
<filein>codec/SMPPMessage.st</filein>

View File

@ -52,6 +52,22 @@ TestCase subclass: SMPPMessageTest [
16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r06]
]
exampleSubmitSM [
^#[16r00 16r00 16r00 16r61 16r00 16r00 16r00 16r04
16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r04
16r00 16r01 16r01 16r39 16r32 16r32 16r35 16r30
16r30 16r31 16r00 16r01 16r01 16r34 16r30 16r30
16r39 16r39 16r39 16r31 16r36 16r00 16r02 16r00
16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r31
16r44 16r69 16r65 16r73 16r20 16r69 16r73 16r74
16r20 16r65 16r69 16r6E 16r65 16r20 16r54 16r65
16r73 16r74 16r6E 16r61 16r63 16r68 16r72 16r69
16r63 16r68 16r74 16r21 16r20 16r20 16r32 16r30
16r31 16r34 16r2D 16r30 16r33 16r2D 16r30 16r31
16r5F 16r31 16r36 16r2E 16r34 16r30 16r2E 16r34
16r32]
]
testReadMessage [
| msg |
msg := SMPPMessage readFrom: self examplePdu readStream.
@ -112,4 +128,13 @@ TestCase subclass: SMPPMessageTest [
msg := SMPPMessage readFrom: self exampleUnbind readStream.
self assert: msg body class equals: SMPPUnbind.
]
testSubmitSM [
| msg |
msg := SMPPMessage readFrom: self exampleSubmitSM readStream.
self assert: msg body class equals:SMPPSubmitSM.
self assert: msg body shortMessage equals: 'Dies ist eine Testnachricht! 2014-03-01_16.40.42'.
self assert: msg body sourceAddress equals: '9225001'.
self assert: msg body destinationAddress equals: '40099916'.
]
]