1
0
Fork 0

lchan: Add a manual test to delay the channel activation ack

Check how OpenBSC will handle the delayed channel activation ack.
This is a manual test only right now.
This commit is contained in:
Holger Hans Peter Freyther 2013-05-02 17:52:54 +02:00
parent 0c12e43d1e
commit c5fae333f8
4 changed files with 95 additions and 4 deletions

78
delay_ack/DelayAck.st Normal file
View File

@ -0,0 +1,78 @@
"
(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.BTS subclass: DelayedAckBTS [
<import: OsmoGSM>
DelayedAckBTS class >> channelWaitDelay [
^8
]
sendRSLActivationAck: aMsg on: aTrx [
Osmo.TimerScheduler instance scheduleInSeconds: 6 block: [
super sendRSLActivationAck: aMsg on: aTrx.
]
]
]
FakeBTS.OpenBSCTest subclass: DelayedAckTest [
<import: OsmoGSM>
createBTS [
^DelayedAckBTS new.
]
requireChannel: aType random: aMask [
| ra rsl lchan |
<category: 'bts'>
"We don't care if it has failed. TODO: share the code with the base."
"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: [^nil].
^ LogicalChannelWrapper initWith: lchan.
]
startTest [
| lchan |
self createAndConnectBTS: '1801/0/0'.
"The ack should be delayed"
lchan := self requireAnyChannel.
self assert: lchan isNil message: 'Channel assignment should fail'.
Transcript nextPutAll: 'Waiting for new line.. press any key to quit'.
stdin next.
]
]
Eval [
DelayedAckTest new
startTest.
]

1
delay_ack/README Normal file
View File

@ -0,0 +1 @@
I'm a manual test to delay the RF Channel Activation ACK message.

View File

@ -64,7 +64,7 @@ RSLChannelActivation extend [
channelNumber: self channelNumber;
frameNumber: #(23 42) asRSLAttributeData;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
aTrx mainBts sendRSLActivationAck: ack toMessage on: aTrx.
]
trxNackChan: aTrx lchan: aLchan [
@ -231,6 +231,10 @@ Object subclass: BTS [
^ OMLBTSInit
]
BTS class >> channelWaitDelay [
^2
]
connect: anAddress [
<category: 'connect'>
self stop.
@ -433,6 +437,10 @@ Object subclass: BTS [
self sendOnPrimaryRSL: aMsg.
]
sendRSLActivationAck: aMsg on: aTrx [
self sendRSL: aMsg on: aTrx
]
findRequestee: aRa [
<category: 'lchan'>
@ -471,7 +479,7 @@ Object subclass: BTS [
self sendOnPrimaryRSL: aMsg.
"Wait for a result and just return the out_chan, remove the entry"
(Delay forSeconds: 2) timedWaitOn: sem.
(Delay forSeconds: self class channelWaitDelay) timedWaitOn: sem.
ras_mutex critical: [ras identityRemove: entry ifAbsent: []].
^ out_chan
]

View File

@ -125,9 +125,13 @@ Object subclass: OpenBSCTest [
bts := aBTS
]
createBTS [
^BTS new
]
createAndConnectBTS [
<category: 'bts'>
bts := BTS new.
bts := self createBTS.
bts connect: 'localhost'.
bts waitForBTSReady.
]
@ -135,7 +139,7 @@ Object subclass: OpenBSCTest [
createAndConnectBTS: aNr [
<category: 'bts'>
bts := BTS new.
bts := self createBTS.
bts
btsId: aNr;
connect: 'localhost';