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/handover/Handover.st

211 lines
5.2 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.
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.
]
]