diff --git a/codec/SMPPBindTransmitterBody.st b/codec/SMPPBindTransmitterBody.st new file mode 100644 index 0000000..e683bdf --- /dev/null +++ b/codec/SMPPBindTransmitterBody.st @@ -0,0 +1,37 @@ +" + (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 . +" + +SMPPBodyBase subclass: SMPPBindTransmitterBody [ + | systemd_id password system_type version addr_ton addr_npi addr_range | + + SMPPBindTransmitterBody class >> messageType [ + ^self bindTransmitter + ] + + SMPPBindTransmitterBody class >> tlvDescription [ + ^OrderedCollection new + add: SMPPSystemdId tlvDescription; + add: SMPPPassword tlvDescription; + add: SMPPSystemType tlvDescription; + add: SMPPInterfaceVersion tlvDescription; + add: SMPPAddressTypeOfNumber tlvDescription; + add: SMPPAddressNumberingPlanIndicator tlvDescription; + add: SMPPAddressRange tlvDescription; + yourself + ] +] diff --git a/codec/SMPPBodyBase.st b/codec/SMPPBodyBase.st new file mode 100644 index 0000000..6021caf --- /dev/null +++ b/codec/SMPPBodyBase.st @@ -0,0 +1,181 @@ +" + (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 | + description := self class tlvDescription. + description do: [:attribute | + attribute isMandatory + ifTrue: [self doParse: attribute stream: aStream]. + attribute isOptional + ifTrue: [^self error: 'Optional attributes not implemented!']. + ] + ] +] diff --git a/codec/SMPPMessage.st b/codec/SMPPMessage.st index 5a8f8e4..2a2822b 100644 --- a/codec/SMPPMessage.st +++ b/codec/SMPPMessage.st @@ -20,13 +20,17 @@ Object subclass: SMPPMessage [ | header body | SMPPMessage class >> readFrom: aStream [ - | len data stream | + | len data stream header body | len := ((aStream next: 4) uintAt: 1) swap32. data := aStream next: len - 4. stream := data readStream. + + header := SMPPPDUHeader readFrom: stream. + body := SMPPBodyBase readFrom: stream for: header. ^SMPPMessage new - header: (SMPPPDUHeader readFrom: stream); - yourself. + header: header; + body: body; + yourself ] header: aHeader [ @@ -41,6 +45,10 @@ Object subclass: SMPPMessage [ body := aBody ] + body [ + ^body + ] + writeOn: aMsg [ | hdrData bodyData | hdrData := header toMessageOrByteArray. diff --git a/codec/attributes/SMPPAddressNumberingPlanIndicator.st b/codec/attributes/SMPPAddressNumberingPlanIndicator.st new file mode 100644 index 0000000..a623d72 --- /dev/null +++ b/codec/attributes/SMPPAddressNumberingPlanIndicator.st @@ -0,0 +1,84 @@ +" + (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 . +" + +Object subclass: SMPPAddressNumberingPlanIndicator [ + + + SMPPAddressNumberingPlanIndicator class [ + npiUnknown [ + + ^2r000 + ] + + npiISDN [ + + ^2r001 + ] + + npiData [ + + ^2r011 + ] + + npiTelex [ + + ^2r100 + ] + + npiLandMobile [ + + ^2r110 + ] + + npiNational [ + + ^2r1000 + ] + + npiPrivate [ + + ^2r1001 + ] + + npiERMES [ + + ^2r1010 + ] + + npiInternet [ + + ^2r1110 + ] + + npiWap [ + + ^2r10010 + ] + ] + + SMPPAddressNumberingPlanIndicator class >> tlvDescription [ + ^Osmo.TLVDescription new + typeKind: Osmo.TLVDescription valueOnly; + instVarName: #addr_npi; parseClass: self; + yourself + ] + + SMPPAddressNumberingPlanIndicator class >> readFrom: aStream with: anAttr [ + ^aStream next + ] +] diff --git a/codec/attributes/SMPPAddressRange.st b/codec/attributes/SMPPAddressRange.st new file mode 100644 index 0000000..22b40f1 --- /dev/null +++ b/codec/attributes/SMPPAddressRange.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 . +" + +SMPPOctetString subclass: SMPPAddressRange [ + + + SMPPAddressRange class >> tlvDescription [ + ^super tlvDescription + instVarName: #addr_range; + minSize: 0 maxSize: 41; + yourself + ] +] diff --git a/codec/attributes/SMPPAddressTypeOfNumber.st b/codec/attributes/SMPPAddressTypeOfNumber.st new file mode 100644 index 0000000..854fae2 --- /dev/null +++ b/codec/attributes/SMPPAddressTypeOfNumber.st @@ -0,0 +1,70 @@ +" + (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 . +" + +Object subclass: SMPPAddressTypeOfNumber [ + + + SMPPAddressTypeOfNumber class [ + + tonUnknown [ + + ^2r000 + ] + + tonInternational [ + + ^2r001 + ] + + tonNational [ + + ^2r010 + ] + + tonNetworkSpecific [ + + ^2r011 + ] + + tonSubscriberNumber [ + + ^2r100 + ] + + tonAlphanumeric [ + + ^2r101 + ] + + tonAbbreviated [ + + ^2r110 + ] + ] + + SMPPAddressTypeOfNumber class >> tlvDescription [ + ^Osmo.TLVDescription new + instVarName: #addr_ton; parseClass: self; + typeKind: Osmo.TLVDescription valueOnly; + yourself + ] + + SMPPAddressTypeOfNumber class >> readFrom: aStream with: anAttribute [ + ^aStream next + ] +] diff --git a/codec/attributes/SMPPInterfaceVersion.st b/codec/attributes/SMPPInterfaceVersion.st new file mode 100644 index 0000000..8725add --- /dev/null +++ b/codec/attributes/SMPPInterfaceVersion.st @@ -0,0 +1,39 @@ +" + (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 . +" + +Object subclass: SMPPInterfaceVersion [ + + + SMPPInterfaceVersion class >> attrVersion34 [ + + ^16r34 + ] + + + SMPPInterfaceVersion class >> tlvDescription [ + ^Osmo.TLVDescription new + instVarName: #version; parseClass: self; + typeKind: Osmo.TLVDescription valueOnly; + valueSize: 1; + yourself + ] + + SMPPInterfaceVersion class >> readFrom: aStream with: anAttribute [ + ^aStream next + ] +] diff --git a/codec/attributes/SMPPOctetString.st b/codec/attributes/SMPPOctetString.st new file mode 100644 index 0000000..cd76502 --- /dev/null +++ b/codec/attributes/SMPPOctetString.st @@ -0,0 +1,41 @@ +" + (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 . +" + +Object subclass: SMPPOctetString [ + + + SMPPOctetString class >> tlvDescription [ + ^Osmo.TLVDescription new + instVarName: #string; parseClass: self; + typeKind: Osmo.TLVDescription valueOnly; + yourself + ] + + SMPPOctetString class >> readFrom: aStream with: anAttribute [ + | str | + str := WriteStream on: String new. + [aStream peek = 0] whileFalse: [ + str nextPut: aStream next asCharacter]. + + "Skip the $0 now" + aStream next. + + "anAttribute... verify the max size" + ^str contents + ] +] diff --git a/codec/attributes/SMPPPassword.st b/codec/attributes/SMPPPassword.st new file mode 100644 index 0000000..2c5d78c --- /dev/null +++ b/codec/attributes/SMPPPassword.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 . +" + +SMPPOctetString subclass: SMPPPassword [ + + + SMPPPassword class >> tlvDescription [ + ^super tlvDescription + instVarName: #password; + minSize: 0 maxSize: 9; + yourself + ] +] diff --git a/codec/attributes/SMPPSystemId.st b/codec/attributes/SMPPSystemId.st new file mode 100644 index 0000000..37921fb --- /dev/null +++ b/codec/attributes/SMPPSystemId.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 . +" + +SMPPOctetString subclass: SMPPSystemdId [ + + + SMPPSystemdId class >> tlvDescription [ + ^super tlvDescription + instVarName: #systemd_id; + minSize: 0 maxSize: 16; + yourself + ] +] diff --git a/codec/attributes/SMPPSystemType.st b/codec/attributes/SMPPSystemType.st new file mode 100644 index 0000000..4447460 --- /dev/null +++ b/codec/attributes/SMPPSystemType.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 . +" + +SMPPOctetString subclass: SMPPSystemType [ + + + SMPPSystemType class >> tlvDescription [ + ^super tlvDescription + instVarName: #system_type; + minSize: 0 maxSize: 13; + yourself + ] +] diff --git a/package.xml b/package.xml index 3c9a7be..335b0c6 100644 --- a/package.xml +++ b/package.xml @@ -4,6 +4,20 @@ OsmoNetwork codec/SMPPPDUHeader.st + + codec/SMPPBodyBase.st + codec/SMPPBindTransmitterBody.st + + codec/attributes/SMPPOctetString.st + codec/attributes/SMPPSystemId.st + codec/attributes/SMPPPassword.st + codec/attributes/SMPPSystemType.st + codec/attributes/SMPPInterfaceVersion.st + codec/attributes/SMPPAddressTypeOfNumber.st + codec/attributes/SMPPAddressNumberingPlanIndicator.st + codec/attributes/SMPPAddressRange.st + + codec/SMPPMessage.st