1
0
Fork 0

handover: Add code for testing handover signalling with OpenBSC

This commit is contained in:
Holger Hans Peter Freyther 2012-12-26 02:37:54 +01:00
parent d54d1648d8
commit 23003259c8
8 changed files with 335 additions and 2 deletions

View File

@ -291,6 +291,41 @@ Object subclass: BTS [
oml_up signal.
]
omlBcchArfcn [
^ site_mgr bts bcchArfcn.
]
findAllocatedLchanOn: aTrx with: aChannelDescription [
| lchan |
"We have the TRX and now need to find the right channel and then the lchan"
aChannelDescription channelType = 1
ifFalse: [^self error: 'Only channel type TCH/F... supported'].
lchan := (aTrx channel: (aChannelDescription timeSlot + 1)) lchan: 1.
lchan isFree ifTrue: [^self error: 'Should have been allocated by the BSC.'].
^ lchan
]
findAllocatedLchan: aChannelDescription [
"Find the given the channel. First find the TRX and then the channel"
Transcript
nextPutAll: 'ARFCN: '; nextPutAll: aChannelDescription arfcn printString;
nextPutAll: ' Type: '; nextPutAll: aChannelDescription channelType printString;
nextPutAll: ' TS: ' ; nextPutAll: aChannelDescription timeSlot printString;
nl;
yourself.
1 to: site_mgr bts availableTrx do: [:nr |
| rc trx |
rc := site_mgr bts radioCarrier: nr.
trx := site_mgr bts basebandTransceiver: nr.
(rc arfcnList includes: aChannelDescription arfcn)
ifTrue: [^self findAllocatedLchanOn: trx with: aChannelDescription].
].
^ self error: 'Failed to find the lchan'
]
stop [
<category: 'control'>
Transcript nextPutAll: 'Stop'; nl.

View File

@ -433,6 +433,7 @@ OMLManagerBase subclass: BTSOML [
btsAttributes: btsAttributes [
<category: 'oml'>
"FIXME: This should be copied into the attributes by GSM 12.21 name"
attributes := btsAttributes.
^ true
]
@ -452,10 +453,15 @@ OMLManagerBase subclass: BTSOML [
ifTrue: [^radio_carrier findObject: fomKey].
^baseband findObject: fomKey.
]
bcchArfcn [
<category: 'accessing'>
^ attributes bcchArfcn.
]
]
OMLManagerBase subclass: RadioCarrierOML [
| id |
| id rcAttributes |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Radio carrier'>
@ -526,9 +532,16 @@ OMLManagerBase subclass: RadioCarrierOML [
radioCarrierAttributes: attributes [
<category: 'oml'>
"TODO: Merge into the attributes"
rcAttributes := attributes.
^ true
]
arfcnList [
"TODO: check for the arfcn list inside the attributes"
^ rcAttributes arfcnList
]
findObject: fomKey [
self fomKey = fomKey
ifTrue: [^self].
@ -682,6 +695,11 @@ Object subclass: LogicalChannel [
sapis := Dictionary new.
]
ts [
<category: 'accessing'>
^ ts
]
ts: aTs [
<category: 'creation'>
ts := aTs

View File

@ -1239,6 +1239,11 @@ OMLDataField subclass: OMLSetBTSAttributes [
^ FOMMessage msgSetBTSAttributes
]
bcchArfcn [
^ (bcch_arfcn data first bitShift: 8)
bitOr: bcch_arfcn data second.
]
OMLSetBTSAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
@ -1456,8 +1461,20 @@ OMLDataField subclass: OMLSetRadioCarrierAttributes [
]
arfcnList [
| list |
<category: 'arfcn_list'>
^ arfcn_list
list := OrderedCollection new.
arfcn_list data size printNl.
"Collect the ARFCNs in the list. Always two together"
1 to: (arfcn_list data size - 1) by: 2 do: [:nr |
| hi low |
hi := arfcn_list data at: nr.
low := arfcn_list data at: nr + 1.
list add: ((hi bitShift: 8) bitOr: low).
].
^ list
]
arfcnList: aList [

View File

@ -97,6 +97,15 @@ Object subclass: LogicalChannelWrapper [
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 [

View File

@ -495,6 +495,16 @@ Object subclass: RSLMessageDefinitions [
^ self dedicatedChannelMessageBase
]
handoverDetectionMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrAccessDelay;
instVarName: #access_delay; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
modeModifyMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
@ -1005,6 +1015,13 @@ RSLDedicatedChannelManagement subclass: RSLSacchDeactivate [
<rslMessageDefinition: #deactivateSacchMessage>
]
RSLDedicatedChannelManagement subclass: RSLHandoverDetection [
| access_delay |
<comment: 'I represent a GSM 08.58 GSM 8.4.7 HANDOVER DETECTION'>
<rslMessageType: #messageDedHandoverDetection>
<rslMessageDefinition: #handoverDetectionMessage>
]
RSLDedicatedChannelManagement subclass: RSLModeModifyRequest [
| channel_mode encr_info main_channel mr mr_control codec |
<comment: 'I represent a GSM 08.58 8.4.9 MODE MODIFY'>

210
handover/Handover.st Normal file
View File

@ -0,0 +1,210 @@
"
(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.
OsmoGSM.GSM48CCProceeding extend [
dispatchForHandoverOn: aTest lchan: aLchan [
<category: '*-HandoverTest'>
]
]
OsmoGSM.GSM48CCConnect extend [
dispatchForHandoverOn: aTest lchan: aLchan [
| ack |
<category: '*-HandoverTest'>
"TODO: The call is now connected.. do something"
ack := GSM48CCConnectAck new
ti: 1; yourself.
aLchan sendGSM: ack toMessage.
]
]
OsmoGSM.GSM48CCConnectAck extend [
dispatchForHandoverOn: aTest lchan: aLchan [
<category: '*-HandoverTest'>
"Actually check for the nack somewhere else?"
]
]
OsmoGSM.GSM48CCRelease extend [
dispatchForHandoverOn: aTest lchan: aLchan [
<category: '*-HandoverTest'>
"TODO: Respond with ReleaseComplete"
]
]
OsmoGSM.GSM48RRChannelModeModify extend [
dispatchForHandoverOn: aTest lchan: aLchan [
| ack |
<category: '*-HandoverTest'>
ack := GSM48RRChannelModeModifyAck new.
ack channelDescription data: self channelDescription data.
ack channelMode mode: self channelMode mode.
aLchan sendGSM: ack toMessage.
]
]
OsmoGSM.GSM48RRChannelRelease extend [
dispatchForHandoverOn: aTest lchan: aLchan [
<category: '*-HandoverTest'>
"Nothing..."
]
]
OsmoGSM.GSM48RRHandoverCommand extend [
dispatchForHandoverOn: aTest lchan: aLchan [
| bts lchan |
"We have the BCCH ARFCN and ARFCN.. try to find it now"
bts := aTest findBCCH: self cellDescription bcch.
lchan := bts findAllocatedLchan: self channelDescription2.
"TODO: return new lchan"
^ lchan
]
]
Object subclass: Handover [
| bts1 bts2 tmsi1 tmsi2 leg1 leg2 number |
<import: OsmoGSM>
<import: FakeBTS>
IMSI1 := '901010000001111'.
IMSI2 := '901010000001112'.
setupCall [
| lchan msg |
lchan := bts1 requireTrafficChannel.
msg := GSM48CMServiceReq new.
msg mi tmsi: tmsi1.
lchan sendGSM: msg toMessage.
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48CMServiceAccept)
ifFalse: [^self error: 'Service is not accepted.'].
"Send the CC Setup now.."
msg := GSM48CCSetup new.
msg ti: 1.
number := msg calledOrDefault.
number encode: GSMCalledBCDNumber typeUnknown
plan: GSMCalledBCDNumber planISDN nr: '40000'.
lchan sendGSM: msg toMessage.
self dispatchUntilRelease: lchan.
]
dispatchUntilRelease: initialLchan [
"Run until the end of the call/channel. No other checking is done."
| stop lchan |
stop := false.
lchan := initialLchan.
[stop] whileFalse: [
| msg res |
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifTrue: [stop := true].
res := msg dispatchForHandoverOn: self lchan: lchan.
(msg isKindOf: GSM48RRHandoverCommand)
ifTrue: [
lchan := LogicalChannelWrapper initWith: res.
lchan sendAccessBurst.
lchan sendGSM: GSM48RRHandoverComplete new toMessage.].
].
]
handlePaging: id [
"Handle paging for TMSI2"
id tmsi = tmsi2
ifFalse: [^self].
"Run it on another process"
[self handlePagingResponse] fork.
]
handlePagingResponse [
| lchan msg ti |
"Handle paging response..."
lchan := bts2 requireTrafficChannel.
msg := GSM48RRPagingResponse new.
msg mi tmsi: tmsi2.
lchan sendGSM: msg toMessage.
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
ti := msg ti bitOr: 8.
(msg isKindOf: GSM48CCSetup)
ifFalse: [^self error: 'Should be a setup message.'].
msg := GSM48CCCallConfirmed new.
msg ti: ti.
lchan sendGSM: msg toMessage.
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelModeModify)
ifTrue: [msg dispatchForHandoverOn: self lchan: lchan]
ifFalse: [^self error: 'No channel mode modify?'].
(Delay forSeconds: 2) wait.
msg := GSM48CCConnect new.
msg ti: ti.
lchan sendGSM: msg toMessage.
"The call is connected now... run until the end."
self dispatchUntilRelease: lchan.
]
test [
"Connect the two bts"
bts1 := OpenBSCTest new
createAndConnectBTS: '1801';
yourself.
bts2 := OpenBSCTest new
createAndConnectBTS: '1903';
yourself.
"Setup paging.."
bts2 bts onPaging: [:id | self handlePaging: id].
"Get TMSIs"
tmsi1 := bts1 allocateTmsi: IMSI1.
tmsi2 := bts2 allocateTmsi: IMSI2.
"Setup the call..."
self setupCall.
]
stopBts [
bts1 stopBts.
bts2 stopBts.
]
findBCCH: aBcch [
<category: 'handover'>
"Find the BTS with the given BCCH... We luckily only have two to
try from.."
bts1 bts omlBcchArfcn = aBcch
ifTrue: [^bts1 bts].
bts2 bts omlBcchArfcn = aBcch
ifTrue: [^bts2 bts].
^ self error: 'Unknown bcch: ', aBcch printString.
]
]

26
handover/HandoverTest.st Normal file
View File

@ -0,0 +1,26 @@
"
(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/>.
"
Eval [
| handover |
FileStream fileIn: 'Handover.st'.
handover := Handover new
test;
stopBts;
yourself.
]

1
handover/README Normal file
View File

@ -0,0 +1 @@
Test Handover