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/BTSDualTrx.st

97 lines
2.8 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/>.
"
"
This is code for a dual trx bts
"
BTS subclass: DualTrxBTS [
| rsl2 |
<category: 'BTS-Core-DualTRX'>
<comment: 'I am a fake dual TRX bts.'>
stop [
<category: 'control'>
rsl2 isNil ifFalse: [rsl2 stop. rsl2 := nil].
^ super stop.
]
omlConnected [
<category: 'control'>
Transcript nextPutAll: 'OML Connected for dual TRX'; nl.
"Create a new SiteManager and forward OML data."
site_mgr := DualTrxSiteManager new
onData: [:each | self sendOML: each];
yourself.
"Forward all RSL data from the TRX."
(site_mgr bts basebandTransceiver: 1)
onData: [:each | rsl send: each];
mainBts: self.
(site_mgr bts basebandTransceiver: 2)
onData: [:each | rsl2 send: each];
mainBts: self.
"Start the OML init now in a new thread"
oml_init := OMLBTSInit initWith: self.
[[oml_init run ] ensure: [Transcript nextPutAll: 'OML-Init exited'; nl]] fork.
]
waitForBTSReady [
<category: 'oml'>
"Wait for one more RSL connection."
oml_up wait.
^ super waitForBTSReady.
]
startRSL: aPort streamId: anId on: aTrx [
^ aTrx fomInstance trx = 0
ifTrue: [super startRSL: aPort streamId: anId on: aTrx]
ifFalse: [self startSecondRSL: aPort streamId: anId on: aTrx].
]
startSecondRSL: aPort streamId: anId on: aTrx [
| trx_id |
"Make sure the RSL id ends with a /1"
trx_id := bts_id copyFrom: 1 to: bts_id size - 1.
trx_id := trx_id , '1'.
rsl2 isNil ifFalse: [rsl2 stop].
rsl2 := BTSRslConnection new
onData: [:each | self handleRsl: each on: aTrx];
onStop: [self rslStopped: rsl2];
onConnect: [self rslConnected: rsl2];
btsId: trx_id;
streamId: anId;
yourself.
rsl2 connect: oml address port: aPort.
]
sendRSL: aMsg on: aTrx [
<category: 'rsl'>
aTrx fomInstance trx = 0
ifTrue: [rsl send: aMsg]
ifFalse: [rsl2 send: aMsg].
]
]