1
0
Fork 0

fakebts: Introduce a dualtrx version of the BTS.

Make it possible to have multiple baseband transceivers. Do this
by putting the code into a DualTrx file (it extends the base classes
with more code). Change the BTS code to use the TRX for dispatching
message.
This commit is contained in:
Holger Hans Peter Freyther 2012-10-08 21:03:15 +02:00
parent c1d6376633
commit abb65601c2
9 changed files with 319 additions and 56 deletions

View File

@ -3,9 +3,11 @@ Eval [
fileIn: 'OMLMsg.st';
fileIn: 'IPAOMLMsg.st';
fileIn: 'OML.st';
fileIn: 'OMLDualTrx.st';
fileIn: 'OMLInit.st';
fileIn: 'RSLMsg.st';
fileIn: 'BTS.st';
fileIn: 'BTSDualTrx.st';
fileIn: 'BTSConnection.st';
fileIn: 'OpenBSCTest.st';
fileIn: 'ExampleTest.st'.

View File

@ -22,39 +22,39 @@ simulating failure condition..."
PackageLoader fileInPackage: #OsmoGSM.
RSLBCCHInformation extend [
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLSACCHFilling extend [
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLMessageBase extend [
btsChannelDispatch: aBTS [
trxChannelDispatch: aTrx [
| ts lchan |
<category: '*-BTS-Core'>
"Generic channel based dispatch."
ts := aBTS trx channel: self channelNumber timeslotNumber + 1.
ts := aTrx channel: self channelNumber timeslotNumber + 1.
lchan := ts lchan: self channelNumber subslotNumber + 1.
self btsDispatchOn: aBTS with: lchan.
self trxDispatchOn: aTrx with: lchan.
]
]
RSLDedicatedChannelManagement extend [
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self btsChannelDispatch: aBTS.
self trxChannelDispatch: aTrx.
]
]
RSLChannelActivation extend [
btsAllocateChan: aBTS lchan: aChan [
trxAllocateChan: aTrx lchan: aChan [
| ack |
<category: '*-BTS-Core'>
@ -64,15 +64,15 @@ RSLChannelActivation extend [
channelNumber: self channelNumber;
frameNumber: #(23 42) asRSLAttributeData;
yourself.
aBTS sendRSL: ack toMessage.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
btsNackChan: aBTS lchan: aLchan [
trxNackChan: aTrx lchan: aLchan [
<category: '*-BTS-Core'>
^ self notYetImplemented
]
btsDispatchOn: aBTS with: lchan [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
"Find the channel and activate it."
Transcript
@ -81,20 +81,20 @@ RSLChannelActivation extend [
"Allocate..."
lchan allocate
ifTrue: [self btsAllocateChan: aBTS lchan: lchan]
ifFalse: [self btsNackChan: aBTS lchan: lchan].
ifTrue: [self trxAllocateChan: aTrx lchan: lchan]
ifFalse: [self trxNackChan: aTrx lchan: lchan].
]
]
RSLRFChannelRelease extend [
btsDispatchOn: aBTS with: lchan [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan releaseRequested.
]
]
RSLImmediateAssignment extend [
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
| gsm ts lchan chan_nr |
<category: '*-BTS-Core'>
self channelNumber isPchAgch
@ -111,47 +111,47 @@ RSLImmediateAssignment extend [
data: (ByteArray with: gsm channelOrPacketDescription data first).
"Find the lchan now."
ts := aBTS trx channel: chan_nr timeslotNumber + 1.
ts := aTrx channel: chan_nr timeslotNumber + 1.
lchan := ts lchan: chan_nr subslotNumber + 1.
"Check that the is allocated."
lchan isFree ifTrue: [^self error: 'The lchan should be allocated.'].
aBTS channelAssigned: lchan ra: gsm requestReference ra.
aTrx mainBts channelAssigned: lchan ra: gsm requestReference ra.
]
]
RSLDataRequest extend [
btsDispatchOn: aBTS with: lchan [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan
dataRequest: self l3Information data
sapi: (self linkIdentifier data first bitAnd: 2r111).
]
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self btsChannelDispatch: aBTS.
self trxChannelDispatch: aTrx.
]
]
RSLSacchDeactivate extend [
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
Transcript nextPutAll: 'Deactivating SACCH. Not doing anything'; nl.
]
]
RSLReleaseRequest extend [
btsDispatchOn: aBTS with: lchan [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan releaseSapiRequest: self linkIdentifier data first.
]
btsDispatchOn: aBTS [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self btsChannelDispatch: aBTS.
self trxChannelDispatch: aTrx.
]
]
@ -211,7 +211,8 @@ Object subclass: BTS [
"Forward all RSL data from the TRX."
site_mgr bts basebandTransceiver
onData: [:each | self sendRSL: each].
onData: [:each | self sendOnPrimaryRSL: each];
mainBts: self.
"Start the OML init now in a new thread"
oml_init := self class omlInitClass initWith: self.
@ -269,15 +270,14 @@ Object subclass: BTS [
[oml txQueueIsEmpty] whileFalse: [(Delay forMilliseconds: 500) wait].
]
startRSL: aPort streamId: anId [
startRSL: aPort streamId: anId on: aTrx [
<category: 'rsl'>
"TODO: handle the stream."
rsl isNil ifFalse: [rsl stop].
rsl := BTSRslConnection new
onData: [:each | self handleRsl: each];
onStop: [self rslStopped];
onConnect: [self rslConnected];
onData: [:each | self handleRsl: each on: aTrx];
onStop: [self rslStopped: rsl];
onConnect: [self rslConnected: rsl];
btsId: bts_id;
streamId: anId;
yourself.
@ -290,14 +290,14 @@ Object subclass: BTS [
bts_id := aId.
]
handleRsl: aMsg [
handleRsl: aMsg on: aTrx [
| rsl |
<category: 'rsl'>
[
| rsl |
rsl := RSLMessageBase parse: aMsg asByteArray readStream.
rsl btsDispatchOn: self.
rsl trxDispatchOn: aTrx.
] on: Exception do: [:e |
Transcript nextPutAll: 'RSL Parsing failed with'; nl.
e inspect.
@ -308,24 +308,29 @@ Object subclass: BTS [
]
]
rslStopped [
rslStopped: anInput [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Stopped'; nl.
]
rslConnected [
rslConnected: anInput [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Connected'; nl.
"Send anything so rsl will be initialized."
rsl send: #(1 2 3 4 5).
anInput send: #(1 2 3 4 5).
oml_up signal.
]
sendRSL: aMsg [
sendOnPrimaryRSL: aMsg [
<category: 'rsl'>
rsl send: aMsg.
]
sendRSL: aMsg on: aTrx [
<category: 'rsl'>
self sendOnPrimaryRSL: aMsg.
]
findRequestee: aRa [
<category: 'lchan'>
@ -361,7 +366,7 @@ Object subclass: BTS [
].
"Send the request"
self sendRSL: aMsg.
self sendOnPrimaryRSL: aMsg.
"Wait for a result and just return the out_chan, remove the entry"
(Delay forSeconds: 2) timedWaitOn: sem.

96
fakebts/BTSDualTrx.st Normal file
View File

@ -0,0 +1,96 @@
"
(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].
]
]

View File

@ -389,12 +389,31 @@ OMLManagerBase subclass: BTSOML [
<category: 'creation'>
radio_carrier := RadioCarrierOML new
parent: self;
id: 1;
yourself.
baseband := BasebandTransceiverOML new
parent: self;
id: 1;
yourself.
]
availableTrx [
<category: 'accessing'>
^ 1
]
radioCarrier: aNr [
<category: 'accessing'>
aNr = 1 ifFalse: [^self error: 'Wrong RadioCarrier number: ', aNr printString].
^ self radioCarrier
]
basebandTransceiver: aNr [
<category: 'accessing'>
aNr = 1 ifFalse: [^self error: 'Wrong Baseband number: ', aNr printString].
^ self basebandTransceiver
]
radioCarrier [
<category: 'accessing'>
^ radio_carrier
@ -436,6 +455,7 @@ OMLManagerBase subclass: BTSOML [
]
OMLManagerBase subclass: RadioCarrierOML [
| id |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Radio carrier'>
@ -492,9 +512,14 @@ OMLManagerBase subclass: RadioCarrierOML [
self basicStart.
]
id: anId [
<category: 'creation'>
id := anId
]
fomInstance [
^ parent fomInstance
trx: 16r0;
trx: id - 1;
ts: 16rFF;
yourself.
]
@ -512,7 +537,7 @@ OMLManagerBase subclass: RadioCarrierOML [
]
OMLManagerBase subclass: BasebandTransceiverOML [
| channels onData |
| channels onData id mainBts |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Baseband Transceiver'>
@ -581,10 +606,15 @@ OMLManagerBase subclass: BasebandTransceiverOML [
channels do: [:each | each start]
]
id: anId [
<category: 'creation'>
id := anId
]
fomInstance [
<category: 'oml'>
^ parent fomInstance
trx: 16r0;
trx: id - 1;
yourself.
]
@ -610,6 +640,16 @@ OMLManagerBase subclass: BasebandTransceiverOML [
<category: 'sending'>
onData value: aMsg.
]
mainBts: aBTS [
<category: 'creation'>
mainBts := aBTS
]
mainBts [
<category: 'access'>
^ mainBts
]
]
OMLChannelCombination extend [

94
fakebts/OMLDualTrx.st Normal file
View File

@ -0,0 +1,94 @@
"
Create a SM, BTS for a dual trx sceneriao
(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/>.
"
SiteManagerOML subclass: DualTrxSiteManager [
<category: 'BTS-OML-DualTRX'>
initialize [
<category: 'creation'>
bts := DualTrxBTSOML new
parent: self;
yourself.
]
]
BTSOML subclass: DualTrxBTSOML [
| rc_two baseband_two |
<category: 'BTS-OML-DualTRX'>
availableTrx [
<category: 'accessing'>
^ 2
]
initialize [
<category: 'creation'>
super initialize.
rc_two := RadioCarrierOML new
parent: self;
id: 2;
yourself.
baseband_two := BasebandTransceiverOML new
parent: self;
id: 2;
yourself.
]
radioCarrier: nr [
<category: 'accessing'>
nr = 1 ifTrue: [^radio_carrier].
nr = 2 ifTrue: [^rc_two].
^ self error: 'RC(%1) not available' % {nr}.
]
basebandTransceiver: nr [
<category: 'accessing'>
nr = 1 ifTrue: [^baseband].
nr = 2 ifTrue: [^baseband_two].
^ self error: 'Baseband(%1) not available' % {nr}.
]
start [
<category: 'accessing'>
attributes := nil.
self basicStart.
(self basebandTransceiver: 1) start.
(self radioCarrier: 1) start.
(self basebandTransceiver: 2) start.
(self radioCarrier: 2) start.
]
findObject: fomKey [
| bb |
<category: 'accessing'>
self fomKey = fomKey
ifTrue: [^self].
fomKey second = radio_carrier class objectClass
ifTrue: [
| rc |
rc := self radioCarrier: (fomKey first trx + 1).
^ rc findObject: fomKey].
bb := self basebandTransceiver: (fomKey first trx + 1).
^ bb findObject: fomKey.
]
]

View File

@ -198,10 +198,10 @@ Object subclass: OMLBTSInit [
^self error: 'Failed to get a (IPA) Formatted O&M message'
]
startRSL: aRsl [
startRSL: aRsl on: aTrx [
| port |
port := (aRsl port data asByteArray ushortAt: 1) swap16.
bts startRSL: port streamId: aRsl streamId data first.
bts startRSL: port streamId: aRsl streamId data first on: aTrx.
^ true
]
@ -238,7 +238,7 @@ Object subclass: OMLBTSInit [
]
btsInit: aSem [
| btsQueue bts init trxProc trxSem rcProc rcSem |
| btsQueue bts init trxSem rcSem |
btsQueue := SharedQueue new.
bts := sm bts.
queues at: bts fomKey put: btsQueue.
@ -251,23 +251,29 @@ Object subclass: OMLBTSInit [
trxSem := Semaphore new.
rcSem := Semaphore new.
init start: [
trxProc := [self trxInit: trxSem] fork.
trxProc name: 'TRX Init process'.
rcProc := [self rcInit: rcSem] fork.
rcProc name: 'Radio-Carrier Init process'.
"Start all trx and radio carriers"
1 to: bts availableTrx do: [:each |
| trxProc rcProc |
trxProc := [self trxInit: trxSem on: (bts basebandTransceiver: each)] fork.
trxProc name: 'TRX(%1) Init process' % {each}.
rcProc := [self rcInit: rcSem on: (bts radioCarrier: each)] fork.
rcProc name: 'Radio-Carrier(%1) Init process' % {each}.
].
].
trxSem wait.
rcSem wait.
"Now wait for all of them to initialize"
1 to: bts availableTrx do: [:each |
trxSem wait.
rcSem wait.
].
bts availabilityStatus state: nil.
bts sendStateChanged.
aSem signal.
]
trxInit: aSem [
| trxQueue trx init msg res ack tss |
trxInit: aSem on: trx [
| trxQueue init msg res ack tss |
trxQueue := SharedQueue new.
trx := sm bts basebandTransceiver.
queues at: trx fomKey put: trxQueue.
"1. Activate the software"
@ -281,7 +287,7 @@ Object subclass: OMLBTSInit [
msg := trxQueue next.
msg omDataField class = IPAOMLRSLConnect
ifFalse: [self error: 'Failed to get the RSL Connect'].
res := self startRSL: msg omDataField.
res := self startRSL: msg omDataField on: trx.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
@ -304,10 +310,9 @@ Object subclass: OMLBTSInit [
aSem signal.
]
rcInit: aSem [
| rcQueue rc init |
rcInit: aSem on: rc [
| rcQueue init |
rcQueue := SharedQueue new.
rc := sm bts radioCarrier.
queues at: rc fomKey put: rcQueue.
"1. Activate the software"

View File

@ -144,6 +144,7 @@ Object subclass: OpenBSCTest [
rsl accessDelay: #(23) asRSLAttributeData.
lchan := bts waitForChannel: rsl toMessage with: ra.
lchan isNil ifTrue: [^self error: 'No LCHAN allocated.'].
^ LogicalChannelWrapper initWith: lchan.
]

View File

@ -537,3 +537,20 @@ TestCase subclass: RSLIETest [
should: [RSLChannelNumber ccchRach subslotNumber] raise: Exception.
]
]
TestCase subclass: DualTrxSiteManagerTest [
<category: 'BTS-OML-DualTRX'>
testCreation [
| sm rc1 rc2 bb1 bb2 |
"Verify we have two RC and two Basebands"
sm := DualTrxSiteManager new.
rc1 := sm bts radioCarrier: 1.
rc2 := sm bts radioCarrier: 2.
bb1 := sm bts basebandTransceiver: 1.
bb2 := sm bts basebandTransceiver: 2.
self deny: rc1 == rc2.
self deny: bb1 == bb2.
]
]

View File

@ -7,10 +7,12 @@
<filein>OMLMsg.st</filein>
<filein>IPAOMLMsg.st</filein>
<filein>OML.st</filein>
<filein>OMLDualTrx.st</filein>
<filein>OMLInit.st</filein>
<filein>RSLMsg.st</filein>
<filein>BTSConnection.st</filein>
<filein>BTS.st</filein>
<filein>BTSDualTrx.st</filein>
<filein>OpenBSCTest.st</filein>
<test>
@ -23,6 +25,7 @@
<sunit>FakeBTS.RSLSmokeTest</sunit>
<sunit>FakeBTS.RSLRoundTripTest</sunit>
<sunit>FakeBTS.RSLIETest</sunit>
<sunit>FakeBTS.DualTrxSiteManagerTest</sunit>
<filein>Test.st</filein>
</test>
</package>