1
0
Fork 0

ussd: Properly encode the processUnstructuredSS request

This commit is contained in:
Holger Hans Peter Freyther 2011-04-01 14:59:18 +02:00
parent abc8326fab
commit 4e11c5a0c7
1 changed files with 20 additions and 1 deletions

View File

@ -16,6 +16,8 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: #OsmoASN1.
Object subclass: GSMDriver [
| sccp proc sapis completeSem phoneConfig |
<category: 'osmo-gsm-operation'>
@ -362,11 +364,28 @@ ProcedureBase subclass: CallProcedure [
ProcedureBase subclass: USSDProcedure [
| nr |
<import: Osmo>
USSDProcedure class >> initWith: aConn phone: aPhone nr: aNr [
^ (super initWith: aConn phone: aPhone)
nr: aNr; yourself
]
USSDProcedure class >> buildProcessUnstructReq: aNr [
| req str |
req := {BERTag fromTuple: #(2 true 1). OrderedCollection
with: {BERTag integer. #(4).}
with: {BERTag integer. #(59).}
with: {BERTag fromTuple: #(0 true 16). OrderedCollection
with: {BERTag octetString. #(15).}
with: {BERTag octetString. aNr asUSSD7Bit.}.}.}.
str := WriteStream on: (ByteArray new: 40).
(DERTLVStream on: str) nextPut: req.
^ str contents
]
nr: aNr [
nr := aNr.
]
@ -388,7 +407,7 @@ ProcedureBase subclass: USSDProcedure [
| 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 facility data: (self class buildProcessUnstructReq: nr).
reg ssVersionOrDefault data: #(0).
conn nextPutData: (BSSAPDTAP initWith: reg linkIdentifier: 0).