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/fakebts/OpenBSCTest.st

260 lines
6.7 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/>.
"
LogicalChannel extend [
sendGSM: aMsg [
<category: '*-OpenBSC-Test'>
self sendGSM: aMsg sapi: 0.
]
sendGSM: aMsg sapi: aSapi [
<category: '*-OpenBSC-Test'>
(self sapiIsEstabliashed: aSapi)
ifTrue: [self sendData: aMsg on: aSapi]
ifFalse: [self establish: aMsg on: aSapi].
]
]
Object subclass: LogicalChannelWrapper [
| sapi0 sapi3 lchan |
<comment: 'I am wrapping a LogicalChannel and provide SAPI
access to it.'>
LogicalChannelWrapper class >> initWith: aLchan [
<category: 'creation'>
^ self new
lchan: aLchan; yourself
]
lchan: aLchan [
<category: 'creation'>
lchan := aLchan.
sapi0 := SharedQueue new.
sapi3 := SharedQueue new.
lchan onDataRequest: [:msg :sapi |
sapi = 0
ifTrue: [sapi0 nextPut: msg].
sapi = 3
ifTrue: [sapi3 nextPut: msg].
].
]
nextSapi0Msg [
<category: 'msg'>
^ sapi0 next
]
nextSapi3Msg [
<category: 'msg'>
^ sapi3 next.
]
sendGSM: aGSM [
<category: 'sending'>
lchan sendGSM: aGSM
]
sendGSM: aGSM sapi: aSapi [
<category: 'sending'>
lchan sendGSM: aGSM sapi: aSapi
]
releaseAllSapis [
<category: 'release'>
Transcript nextPutAll: 'Releasing all SAPIs of the channel'; nl.
(lchan sapiIsEstabliashed: 0)
ifTrue: [lchan releaseSapi: 0].
(lchan sapiIsEstabliashed: 3)
ifTrue: [lchan releaseSapi: 3].
]
onReleaseReqCB: aCb [
<category: 'release'>
lchan onReleaseReqCB: aCb
]
cancel [
<category: 'release'>
sapi0 nextPut: nil.
sapi3 nextPut: nil.
]
sendAccessBurst [
| msg |
<category: 'handover'>
msg := RSLHandoverDetection new
channelNumber: lchan channelNumber;
yourself.
lchan ts forwardRsl: msg toMessage.
]
]
Object subclass: OpenBSCTest [
| bts testFailed |
<category: 'OpenBSC-Test'>
<comment: 'I help in dealing with setup and teardown of a test'>
<import: OsmoGSM>
OpenBSCTest class >> initWith: aBTS [
<category: 'creation'>
^ self new
bts: aBTS; yourself.
]
bts: aBTS [
<category: 'creation'>
bts := aBTS
]
createAndConnectBTS [
<category: 'bts'>
bts := BTS new.
bts connect: 'localhost'.
bts waitForBTSReady.
]
createAndConnectBTS: aNr [
<category: 'bts'>
bts := BTS new.
bts
btsId: aNr;
connect: 'localhost';
waitForBTSReady.
]
bts [
<category: 'accessing'>
^ bts
]
stopBts [
<category: 'bts'>
bts stop.
]
requireChannel: aType random: aMask [
| ra rsl lchan |
<category: 'bts'>
"The RA we will wait for.."
ra := aType bitOr: (Random between: 0 and: aMask).
rsl := RSLChannelRequired new.
rsl channelNumber: RSLChannelNumber ccchRach.
rsl requestReference: {ra. 42. 20} asRSLAttributeData.
rsl accessDelay: #(23) asRSLAttributeData.
lchan := bts waitForChannel: rsl toMessage with: ra.
lchan isNil ifTrue: [^self error: 'No LCHAN allocated.'].
^ LogicalChannelWrapper initWith: lchan.
]
requireAnyChannel [
<category: 'bts'>
" Only use four bit for random to work with both necis"
^ self requireChannel: 2r0 random: 2r1111
]
requireEmergencyChannel [
<category: 'bts'>
^ self requireChannel: 2r10100000 random: 2r11111
]
requireTrafficChannel [
<category: 'bts'>
"Originating speech call from dual-rate mobile station when TCH/H
is sufficient and supported by the MS for speech calls and the network"
^ self requireChannel: 2r01000000 random: 2r1111.
]
assert: aBoolean message: aMessage [
<category: 'verifying'>
aBoolean ifTrue: [^self].
Transcript nextPutAll: 'TEST: Failure with ', aMessage; nl.
testFailed := true.
]
deny: aBoolean message: aMessage [
<category: 'verifying'>
self assert: aBoolean not message: aMessage.
]
failed [
<category: 'verifying'>
^ testFailed
]
allocateTmsi: imsi [
| tmsi lchan lu msg |
"Do a LU and get the TMSI."
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send the LU request"
lu := GSM48LURequest new.
lu lai
mcc: 1;
mnc: 1;
lac: 1.
lu mi imsi: imsi.
lchan sendGSM: lu toMessage.
"Now deal with what the NITB wants"
"4.1 Send the IMEI..."
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48IdentityReq)
ifFalse: [^self error: 'Wanted identity request'].
(msg idType isIMEI)
ifFalse: [^self error: 'Wanted IMEI reqest'].
msg := GSM48IdentityResponse new.
msg mi imei: '6666666666666666'.
lchan sendGSM: msg toMessage.
"4.2 LU Accept"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48LUAccept)
ifFalse: [^self error: 'LU failed'].
tmsi := msg mi tmsi.
msg := GSM48TMSIReallocationComplete new.
lchan sendGSM: msg toMessage.
"4.3 MM Information for the time. ignore it"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48MMInformation)
ifFalse: [^self error: 'MM Information'].
"4.4 release.. if we now don't close the LCHAN it will
remain open for a bit. OpenBSC should and will start the
approriate timer soon(tm)"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifFalse: [^self error: 'RR Channel Release'].
"4.5.. be nice... for now and send a disconnect."
lchan releaseAllSapis.
^ tmsi.
]
]