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

smpp: Add setter to SMPPDeliverySM and introduce SMPPCommand

The setters were developed under Pharo (what a breeze!) and the
final SMPPConnection changes were done using GNU Smalltalk.
This commit is contained in:
Holger Hans Peter Freyther 2014-07-21 10:04:30 +02:00
parent d22a3e248a
commit 22f907bf63
5 changed files with 169 additions and 19 deletions

View File

@ -32,7 +32,8 @@ TEST = \
CONNECTION = \
./connection/Extensions.st \
./connection/SMPPConnection.st
./connection/SMPPConnection.st \
./connection/SMPPCommand.st
CODEC = \
./codec/attributes/SMPPOctetString.st \

View File

@ -95,4 +95,80 @@ SMPPBodyBase subclass: SMPPDeliverSM [
<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
]
]

64
connection/SMPPCommand.st Normal file
View File

@ -0,0 +1,64 @@
Object subclass: SMPPCommand [
| body onTimeout onResult onError timeoutTimer connection |
<category: 'SMPP-Connection'>
<comment: ''>
SMPPCommand class >> initWith: aBody [
^self new
body: aBody;
yourself
]
messageType [
^body class messageType
]
body [
^body
]
body: aBody [
<category: 'creation'>
body := aBody
]
onResult: aBlock [
<category: 'creation'>
onResult := aBlock
]
onError: aBlock [
<category: 'creation'>
onError := aBlock
]
onTimeout: aBlock [
<category: 'creation'>
onTimeout := aBlock
]
scheduledOn: aConnection [
connection := aConnection.
timeoutTimer := Osmo.TimerScheduler instance
scheduleInSeconds: 10 block: [self timeout].
]
timeout [
<category: 'result dispatch'>
onTimeout ifNotNil: [:block | block value].
]
error: anError [
<category: 'result dispatch'>
timeoutTimer cancel.
onError ifNotNil: [:block | block value: anError].
]
result: aResult [
<category: 'result dispatch'>
timeoutTimer cancel.
onResult ifNotNil: [:block | block value: aResult].
]
]

View File

@ -38,12 +38,8 @@ Osmo.OsmoStreamSocketBase subclass: SMPPConnection [
]
scheduleBindTrx [
| header body |
| command body |
header := SMPPPDUHeader new
commandId: SMPPBindTransceiver messageType;
commandStatus: 0;
yourself.
body := SMPPBindTransceiver new
systemId: systemId;
password: password;
@ -53,23 +49,35 @@ Osmo.OsmoStreamSocketBase subclass: SMPPConnection [
typeOfNumber: 0;
addressRange: #[];
yourself.
self send: (SMPPMessage new
header: header;
body: body) onResponse: [:resp | ].
command := SMPPCommand initWith: body.
self scheduleCommand: command.
]
send: aMessage onResponse: aBlock [
| seq key |
scheduleCommand: aCommand [
aCommand scheduledOn: self.
self send: aCommand.
]
send: aCommand [
| seq key header message |
seq := nextSeq.
nextSeq := nextSeq + 1.
aMessage header sequenceNumber: seq.
header := SMPPPDUHeader new
sequenceNumber: seq;
commandId: aCommand messageType;
commandStatus: 0;
yourself.
message := SMPPMessage new
header: header;
body: aCommand body;
yourself.
"Remember that we want a response. TODO add timeout handling"
pendingCommands at: seq put: aBlock.
writeQueue nextPut: aMessage toMessage asByteArray
pendingCommands at: seq put: aCommand.
writeQueue nextPut: message toMessage asByteArray
]
connect [
@ -113,13 +121,13 @@ Osmo.OsmoStreamSocketBase subclass: SMPPConnection [
]
receviedResponse: aMessage [
| seq block |
| seq command |
"Search for a response"
seq := aMessage header sequenceNumber.
block := pendingCommands removeKey: seq ifAbsent: [
command := pendingCommands removeKey: seq ifAbsent: [
"TODO: log it"
^false].
block value: aMessage
command result: aMessage.
]
]

View File

@ -42,6 +42,7 @@
<filein>codec/SMPPMessage.st</filein>
<filein>connection/SMPPConnection.st</filein>
<filein>connection/SMPPCommand.st</filein>
<filein>connection/Extensions.st</filein>
<test>