1
0
Fork 0

ussd: Add a very simple widget to send USSD requests to the netwrok

This will only send processUnstructuredSS-Request and right now
the number is hardcoded. It will be better.
This commit is contained in:
Holger Hans Peter Freyther 2011-04-01 13:16:02 +02:00
parent 716e4ac30c
commit abc8326fab
3 changed files with 73 additions and 3 deletions

View File

@ -1,5 +1,5 @@
"
(C) 2010 by Holger Hans Peter Freyther
(C) 2010-2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -358,3 +358,46 @@ ProcedureBase subclass: CallProcedure [
].
]
]
ProcedureBase subclass: USSDProcedure [
| nr |
USSDProcedure class >> initWith: aConn phone: aPhone nr: aNr [
^ (super initWith: aConn phone: aPhone)
nr: aNr; yourself
]
nr: aNr [
nr := aNr.
]
createConnection: aHandler phone: aPhone [
| cm |
cm := GSM48CMServiceReq new.
cm mi imsi: aPhone imsi.
cm keyAndType val: 8.
self openConnection: cm sapi: 0 phone: aPhone handler: aHandler.
]
name [
^ 'USSD Procedure'
]
serviceAccepted [
| reg |
reg := GSM48SSRegister new.
reg facility data: #(16rA1 16r13 16r02 16r01 16r04 16r02 16r01 16r3B 16r30 16r0B 16r04 16r01 16r0F 16r04 16r06 16r2A 16rD5 16r4C 16r16 16r1B 16r01) asByteArray.
reg ssVersionOrDefault data: #(0).
conn nextPutData: (BSSAPDTAP initWith: reg linkIdentifier: 0).
]
handleData: aMsg sapi: aSapi [
aMsg class messageType = GSM48SSMessage msgReleaseCompl ifTrue:[
aMsg inspect.
self success: true.
]
]
]

View File

@ -1,5 +1,5 @@
"
(C) 2010 by Holger Hans Peter Freyther
(C) 2010-2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -138,6 +138,14 @@ Object subclass: IPAConfig [
callNumber: aPhone nr: aNumber [
^ (self doCallNumber: aPhone nr: aNumber) execute
]
doUSSD: aPhone nr: aNr [
^ USSDProcedure initWith: (connection sccpHandler) phone: aPhone nr: aNr.
]
sendUSSD: aPhone nr: aNr [
^ (self doUSSD: aPhone nr: aNr) execute
]
]
Object subclass: PhoneConfig [

View File

@ -150,6 +150,20 @@ ProcedureWidget subclass: CallWidget [
]
]
ProcedureWidget subclass: USSDWidget [
contents [
^[:e |
e form build: [:form |
form input action: [:val | self doUSSD: val].
form button text: 'USSD']
]
]
doUSSD: aNumber [
self runProcedure: [self application gsmServer doUSSD: self session gsmConfig nr: aNumber] name: 'USSD'.
]
]
Iliad.ILWidget subclass: ProcedureWidget [
showStatus: item on: form [
| status |
@ -205,7 +219,7 @@ Iliad.ILSession subclass: GSMTestphoneSession [
]
Iliad.ILApplication subclass: GSMTestphoneApp [
| config call lu serverConfig gsmServer procedureWidget |
| config call lu serverConfig gsmServer procedureWidget ussd |
GSMTestphoneApp class >> path [ ^ 'testphone' ]
GSMTestphoneApp class >> initialize [
@ -236,6 +250,10 @@ Iliad.ILApplication subclass: GSMTestphoneApp [
^ lu ifNil: [lu := LUWidget new]
]
ussd [
^ ussd ifNil: [ussd := USSDWidget new]
]
index [
<category: 'controllers'>
^ [:e |
@ -245,6 +263,7 @@ Iliad.ILApplication subclass: GSMTestphoneApp [
build: self phoneConfig;
build: self lu;
build: self call;
build: self ussd;
build: self procedures.
].
]