1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-openbsc-test/ussd/USSDTest.st

87 lines
2.4 KiB
Smalltalk

"
(C) 2012 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/>.
"
PackageLoader fileInPackage: #FakeBTS.
FakeBTS.OpenBSCTest subclass: USSDTest [
<import: OsmoGSM>
USSDTest class >> registerMessage [
^#[16r1B 16r3B 16r1C 16r15 16rA1 16r13 16r02
16r01 16r04 16r02 16r01 16r3B 16r30 16r0B
16r04 16r01 16r0F 16r04 16r06 16rAA 16r51
16r0C 16r06 16r1B 16r01 16r7F 16r01 16r00]
]
USSDTest class >> nokiaRegisterSS [
^#[11 123 28 13 161 11 2 1 3 2 1 14 48 3 4 1 33 127 1 0]
]
USSDTest class >> interrogateSS [
^#[16r1B 16r7B 16r1C 16r0D 16rA1 16r0B 16r02
16r01 16r01 16r02 16r01 16r0E 16r30 16r03
16r04 16r01 16r11 16r7F 16r01 16r00]
]
startTest [
self createAndConnectBTS: '1801/0/0'.
self
testUSSDMessage
]
expect: aClass from: aLchan [
| msg |
msg := GSM48MSG decode: aLchan nextSapi0Msg readStream.
(msg isKindOf: aClass)
ifFalse: [^self error: 'Got wrong type wanted ', aClass name asString, ' got ', msg class asString].
]
testUSSDMessage [
| tmsi cm lchan msg |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send a CM Service Request "
cm := GSM48CMServiceReq new.
cm mi tmsi: tmsi.
lchan sendGSM: cm toMessage.
self expect: GSM48CMServiceAccept from: lchan.
"4. USSD messages"
lchan sendGSM: self class nokiaRegisterSS sapi: 0.
"5. Read message"
self expect: GSM48SSReleaseComplete from: lchan.
]
]
Eval [
| test |
test := USSDTest new
startTest;
stopBts;
yourself.
ObjectMemory quit: 23
]