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/delay_ack/DelayAck.st

118 lines
3.3 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.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.BTS subclass: DelayedReleaseAckBTS [
<comment: 'I will delay RSLRFChannelReleaseAck messages causing the channels
to be marked as broken in the BSC/NITB or at least that is the plan.'>
sendOnPrimaryRSL: aMsg [
| rsl |
"We need to decode the message and check if it is a ChannelReleaseACK
and we will delay it then..."
rsl := RSLMessageBase parse: aMsg readStream.
rsl class = FakeBTS.RSLRFChannelReleaseAck
ifTrue: [Osmo.TimerScheduler instance scheduleInSeconds: 6 block:
[super sendOnPrimaryRSL: aMsg]]
ifFalse: [super sendOnPrimaryRSL: aMsg].
]
]
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 to continue'.
stdin next.
]
]
FakeBTS.OpenBSCTest subclass: DelayedReleaseAckTest [
<import: OsmoGSM>
createBTS [
^DelayedReleaseAckBTS new
]
startTest [
| lchan |
self createAndConnectBTS: '1801/0/0'.
lchan := self requireAnyChannel.
self deny: lchan isNil message: 'Channel assignment should work'.
Transcript nextPutAll: 'Waiting for new line.. press to quit'.
stdin next.
]
]
Eval [
DelayedAckTest new
startTest.
DelayedReleaseAckTest new
startTest.
]