smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Add 'osmo-st-openbsc-test/' from commit '4cd403960d34a240e9613e01cbe2e21c9e5918b9'

git-subtree-dir: osmo-st-openbsc-test
git-subtree-mainline: d27132a75e
git-subtree-split: 4cd403960d
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:03 +02:00
commit 9cda4fc259
50 changed files with 8580 additions and 0 deletions

2
osmo-st-openbsc-test/.gitignore vendored Normal file
View File

@ -0,0 +1,2 @@
*.sw?
*.py?

View File

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

View File

@ -0,0 +1 @@
I'm a manual test to delay the RF Channel Activation ACK message.

View File

@ -0,0 +1,91 @@
"
(C) 2014 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.RSLEstablishRequest extend [
trxDispatchOn: aTrx with: lchan [
| msg |
<category: '*-BTS-Core'>
'Got an establish request.' printNl.
msg := FakeBTS.RSLConnectionFailure new
channelNumber: self channelNumber;
cause: #[1] asRSLAttributeData;
yourself.
aTrx mainBts sendRSL: msg toMessage on: aTrx.
msg := FakeBTS.RSLReleaseIndication new
channelNumber: self channelNumber;
linkIdentifier: self linkIdentifier;
yourself.
aTrx mainBts sendRSL: msg toMessage on: aTrx.
msg := FakeBTS.RSLErrorIndication new
channelNumber: self channelNumber;
linkIdentifier: self linkIdentifier;
rlmCause: #[1] asRSLAttributeData;
yourself.
aTrx mainBts sendRSL: msg toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self trxChannelDispatch: aTrx.
]
]
FakeBTS.OpenBSCTest subclass: DoubleRelease [
| tmsi |
IMSI := '901010000001111'.
startTest [
self createAndConnectBTS: '1234/0/0'.
bts onPaging: [:id | self handlePaging: id].
tmsi := self allocateTmsi: IMSI.
]
handlePaging: id [
"Handle paging for TMSI2"
id tmsi = tmsi ifFalse: [^self].
"Run it on another process"
[self handlePagingResponse] fork.
]
handlePagingResponse [
| lchan msg ti |
"Handle paging response..."
lchan := self requireAnyChannel.
msg := GSM48RRPagingResponse new.
msg mi tmsi: tmsi.
lchan sendGSM: msg toMessage.
Semaphore new wait.
]
]
Eval [
DoubleRelease new
startTest.
'Waiting to the end' printNl.
Semaphore new wait.
]

View File

@ -0,0 +1,35 @@
This tests some odd LAPDm and MS behavior that leads to a double
RF Channel Release by the BSC/NITB.
It is a manual test right now. After the LU a SMS needs to be
queued through the VTY and then the error/failure sequence will
be sent to the BSC.
The test is passed when no exceptions like the below are raised
An instance of SystemExceptions.NotFound
creator: Dictionary (
)
tag: an Object
messageText: 'key not found'
resumeBlock: a BlockClosure
onDoBlock: a BlockClosure
handlerBlock: a BlockClosure
context: BlockClosure>>on:do: (BlkClosure.st:196)
isNested: nil
previousState: 0
value: 0
With data: ByteArray (2 7 1 32 2 0 20 1 )
RSL Parsing failed with
An instance of Error
creator: a LogicalChannel
tag: an Object
messageText: 'Lchan was not allocated.'
resumeBlock: a BlockClosure
onDoBlock: a BlockClosure
handlerBlock: a BlockClosure
context: BlockClosure>>on:do: (BlkClosure.st:196)
isNested: nil
previousState: 0
With data: ByteArray (8 46 1 32 )

View File

@ -0,0 +1,14 @@
Eval [
FileStream
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

@ -0,0 +1,522 @@
"
(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 a fake base station used for injecting RSL/DTAP messages and
simulating failure condition..."
PackageLoader fileInPackage: #OsmoGSM.
RSLBCCHInformation extend [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLSACCHFilling extend [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLMessageBase extend [
trxChannelDispatch: aTrx [
| ts lchan |
<category: '*-BTS-Core'>
"Generic channel based dispatch."
ts := aTrx channel: self channelNumber timeslotNumber + 1.
lchan := ts lchan: self channelNumber subslotNumber + 1.
self trxDispatchOn: aTrx with: lchan.
]
]
RSLDedicatedChannelManagement extend [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self trxChannelDispatch: aTrx.
]
]
RSLChannelActivation extend [
trxAllocateChan: aTrx lchan: aChan [
| ack |
<category: '*-BTS-Core'>
Transcript nextPutAll: 'Allocated channel'; nl.
ack := RSLChannelActivationAck new
channelNumber: self channelNumber;
frameNumber: #(23 42) asRSLAttributeData;
yourself.
aTrx mainBts sendRSLActivationAck: ack toMessage on: aTrx.
]
trxNackChan: aTrx lchan: aLchan [
<category: '*-BTS-Core'>
^ self notYetImplemented
]
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
"Find the channel and activate it."
Transcript
nextPutAll: 'Channel Activation: ';
nextPutAll: self channelNumber subslotNumber asString; nl.
"Allocate..."
lchan allocate
ifTrue: [self trxAllocateChan: aTrx lchan: lchan]
ifFalse: [self trxNackChan: aTrx lchan: lchan].
]
]
RSLRFChannelRelease extend [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan releaseRequested.
]
]
RSLImmediateAssignment extend [
trxDispatchOn: aTrx [
| gsm ts lchan chan_nr |
<category: '*-BTS-Core'>
self channelNumber isPchAgch
ifFalse: [^self error: 'Can only handle assignment on PCH/AGCH'].
"Skip the L2 Pseudo length"
gsm := OsmoGSM.GSM48MSG decode:
(self fullL3Info readStream skip: 1; yourself).
"Convert the GSM 04.08 10.5.2.5 Channel Description to a RSL
Channel number. Do it by copying the first byte. This makes no
differentation between channel or packet description right now"
chan_nr := RSLChannelNumber new
data: (ByteArray with: gsm channelOrPacketDescription data first).
"Find the lchan now."
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.'].
aTrx mainBts channelAssigned: lchan ra: gsm requestReference ra.
]
]
RSLDataRequest extend [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan
dataRequest: self l3Information data
sapi: (self linkIdentifier data first bitAnd: 2r111).
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self trxChannelDispatch: aTrx.
]
]
RSLSacchDeactivate extend [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan
dataRequest: self l3Information data
sapi: (self linkIdentifier data first bitAnd: 2r111).
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
Transcript nextPutAll: 'Deactivating SACCH. Not doing anything'; nl.
]
]
RSLEncryptionCommand extend [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan
dataRequest: self l3Information data
sapi: (self linkIdentifier data first bitAnd: 2r111).
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self trxChannelDispatch: aTrx.
]
]
RSLModeModifyRequest extend [
trxDispatchOn: aTrx with: lchan [
| ack |
<category: '*-BTS-Core'>
ack := RSLModeModifyAck new
channelNumber: self channelNumber;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
self trxChannelDispatch: aTrx.
]
]
RSLReleaseRequest extend [
trxDispatchOn: aTrx with: lchan [
<category: '*-BTS-Core'>
lchan releaseSapiRequest: self linkIdentifier data first.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self trxChannelDispatch: aTrx.
]
]
RSLIPACreateConnection extend [
trxDispatchOn: aTrx with: lchan [
| ack |
<category: '*-BTS-Core'>
lchan ipaConnId: aTrx mainBts newConnectionIdentifier asRSLAttributeData.
ack := RSLIPACreateConnectionAck new
channelNumber: lchan channelNumber;
connectionIdentifier: lchan ipaConnId;
localPort: #(23 42) asRSLAttributeData;
localIP: #(0 0 0 0) asRSLAttributeData;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self trxChannelDispatch: aTrx.
]
]
RSLIPAModifyConnection extend [
trxDispatchOn: aTrx with: lchan [
| ack |
<category: '*-BTS-Core'>
ack := RSLIPAModifyConnectionAck new
channelNumber: lchan channelNumber;
connectionIdentifier: lchan ipaConnId;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self trxChannelDispatch: aTrx.
]
]
RSLPagingCommand extend [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
aTrx mainBts paging: self msIdenity.
]
]
Object subclass: BTS [
| site_mgr oml rsl oml_queue oml_init connected oml_up ras ras_mutex
bts_id on_paging last_conn_id |
<category: 'BTS-Core'>
<comment: 'A fake BTS to test the state machine and inject
RSL messages to test a network without RF.'>
BTS class >> omlInitClass [
^ OMLBTSInit
]
BTS class >> channelWaitDelay [
^2
]
connect: anAddress [
<category: 'connect'>
self stop.
rsl := nil.
last_conn_id := 0.
oml := BTSOmlConnection new
onData: [:each | self handleOml: each];
onStop: [self omlStopped];
onConnect: [self omlConnected];
btsId: bts_id;
yourself.
"Make sure oml is fully assigned"
oml_up := Semaphore new.
oml_queue := SharedQueue new.
ras := OrderedCollection new.
ras_mutex := Semaphore forMutualExclusion.
oml connect: anAddress
]
siteManager [
<category: 'control'>
^ site_mgr
]
trx [
<category: 'control'>
^ site_mgr bts basebandTransceiver
]
omlStopped [
<category: 'control'>
Transcript nextPutAll: 'OML Connection gone.'; nl.
]
omlConnected [
<category: 'control'>
Transcript nextPutAll: 'OML Connected'; nl.
"Create a new SiteManager and forward OML data."
site_mgr := SiteManagerOML new
onData: [:each | self sendOML: each];
yourself.
"Forward all RSL data from the TRX."
site_mgr bts basebandTransceiver
onData: [:each | self sendOnPrimaryRSL: each];
mainBts: self.
"Start the OML init now in a new thread"
oml_init := self class omlInitClass initWith: self.
[[oml_init run ] ensure: [Transcript nextPutAll: 'OML-Init exited'; nl]] fork.
]
omlUp [
<category: 'oml'>
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.
rsl isNil ifFalse: [rsl stop. rsl := nil].
oml isNil ifFalse: [oml stop. oml := nil].
oml_init isNil ifFalse: [oml_queue nextPut: nil. oml_init := nil].
]
sendOML: aMsg [
<category: 'oml'>
oml send: aMsg.
]
waitForOMLMsg [
<category: 'oml'>
"TODO: do something funny with continuations"
^ oml_queue next
]
handleOml: aMsg [
<category: 'oml'>
[
| oml |
oml := OMLMessageBase parse: aMsg asByteArray readStream.
oml_queue nextPut: oml.
] on: Exception do: [:e |
Transcript nextPutAll: 'OML Parsing failed with'; nl.
e inspect.
Transcript
nextPutAll: 'With data: ';
nextPutAll: aMsg asByteArray printString;
nl.
]
]
waitForBTSReady [
<category: 'oml'>
oml_up wait.
oml_up wait.
"Wait for OML queue to be empty. TODO: get a cb when last message
was processed."
[oml txQueueIsEmpty] whileFalse: [(Delay forMilliseconds: 500) wait].
]
startRSL: aPort streamId: anId on: aTrx [
<category: 'rsl'>
rsl isNil ifFalse: [rsl stop].
rsl := BTSRslConnection new
onData: [:each | self handleRsl: each on: aTrx];
onStop: [self rslStopped: rsl];
onConnect: [self rslConnected: rsl];
btsId: bts_id;
streamId: anId;
yourself.
rsl connect: oml address port: aPort.
]
btsId: aId [
<category: 'bts'>
bts_id := aId.
]
handleRsl: aMsg on: aTrx [
| rsl |
<category: 'rsl'>
[
| rsl |
rsl := RSLMessageBase parse: aMsg asByteArray readStream.
rsl trxDispatchOn: aTrx.
] on: Exception do: [:e |
Transcript nextPutAll: 'RSL Parsing failed with'; nl.
e inspect.
Transcript
nextPutAll: 'With data: ';
nextPutAll: aMsg asByteArray printString;
nl.
]
]
rslStopped: anInput [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Stopped'; nl.
]
rslConnected: anInput [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Connected'; nl.
"Send anything so rsl will be initialized."
anInput send: #(1 2 3 4 5).
oml_up signal.
]
sendOnPrimaryRSL: aMsg [
<category: 'rsl'>
rsl send: aMsg.
]
sendRSL: aMsg on: aTrx [
<category: 'rsl'>
self sendOnPrimaryRSL: aMsg.
]
sendRSLActivationAck: aMsg on: aTrx [
self sendRSL: aMsg on: aTrx
]
findRequestee: aRa [
<category: 'lchan'>
ras_mutex critical: [
ras do: [:each |
each key = aRa
ifTrue: [^each]]].
^ self error: 'Failed to find RA: ', aRa displayString.
]
channelAssigned: aLchan ra: aRa [
| requestee |
<category: 'lchan'>
"Find and remove the requestee"
requestee := self findRequestee: aRa.
ras_mutex critical: [
ras identityRemove: requestee.
].
"Inform about the new channel"
requestee value value: aLchan.
]
waitForChannel: aMsg with: ra [
| sem out_chan entry |
sem := Semaphore new.
"Insert the callback"
entry := ra -> [:lchan | out_chan := lchan. sem signal].
ras_mutex critical: [
ras add: entry.
].
"Send the request"
self sendOnPrimaryRSL: aMsg.
"Wait for a result and just return the out_chan, remove the entry"
(Delay forSeconds: self class channelWaitDelay) timedWaitOn: sem.
ras_mutex critical: [ras identityRemove: entry ifAbsent: []].
^ out_chan
]
paging: aPaging [
on_paging ifNotNil: [on_paging value: aPaging]
]
onPaging: aCallback [
on_paging := aCallback
]
newConnectionIdentifier [
last_conn_id := last_conn_id + 1.
^ ByteArray
with: ((last_conn_id bitShift: -8) bitAnd: 16rFF)
with: (last_conn_id bitAnd: 16rFF)
]
]

View File

@ -0,0 +1,291 @@
"
(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: #Sockets;
fileInPackage: #OsmoCore;
fileInPackage: #OsmoNetwork.
Osmo.IPAProtoHandler subclass: BTSIPAProtoHandler [
| on_id_get id |
<category: 'BTS-Core'>
<comment: 'ID Get'>
<import: Osmo>
onIdGet: aBlock [
<category: 'connection'>
on_id_get := aBlock
]
btsId: anId [
<category: 'creation'>
"Set the BTS ID"
id := anId
]
handleIdGet: aMsg [
| name in_msg out_msg unit_id |
name := 'BTS Test'.
"null terminate the string"
unit_id := (WriteStream on: (ByteArray new: 6))
nextPutAll: id asByteArray;
nextPut: 16r0;
contents.
in_msg := IPAMsgRequest parse: aMsg asByteArray readStream.
out_msg := IPAMsgResponse new
type: IPAConstants msgIdResp;
data: (Array
with: (16r8->unit_id));
yourself.
muxer nextPut: out_msg toMessage asByteArray with: IPAConstants protocolIPA.
"Inform about the request"
on_id_get value.
]
]
Object subclass: BTSConnectionBase [
| socket txQueue mux demux rxDispatch rxProc txProc stopped
onData onStop onConnect connected address btsId streamId |
<category: 'BTS-Core'>
<comment: 'I am the base class for the OML and RSL connection
to the BSC'>
<import: Osmo>
BTSConnectionBase class >> new [
<category: 'creation'>
^ super new
initialize;
yourself.
]
initialize [
<category: 'creation'>
stopped := false.
]
btsId: anId [
<category: 'creation'>
btsId := anId
]
btsId [
<category: 'query'>
^ btsId ifNil: ['1801/0/0']
]
streamId: anId [
<category: 'creation'>
streamId := anId
]
streamId [
<category: 'query'>
^ streamId ifNil: [self class ipaPrototype]
]
connect: anAddress [
<category: 'connect'>
^ self connect: anAddress port: self class defaultPort
]
address [
<category: 'accessing'>
^ address
]
txQueueIsEmpty [
<category: 'accessing'>
^ txQueue isEmpty.
]
connect: anAddress port: aPort[
| proto_handler |
<category: 'connect'>
address := anAddress.
socket := Sockets.StreamSocket remote: anAddress port: aPort.
txQueue := SharedQueue new.
demux := IPADemuxer initOn: socket.
mux := IPAMuxer initOn: txQueue.
rxDispatch := IPADispatcher new.
proto_handler := BTSIPAProtoHandler new
token: '1801';
registerOn: rxDispatch;
muxer: mux;
onIdGet: [self gotIdRequest];
btsId: self btsId;
yourself.
self streamConnected.
stopped := false.
connected := false.
"Now start the input/output process"
rxProc := [
Processor activeProcess name: self class name, ' RX'.
[stopped] whileFalse: [self processOne].
] fork.
txProc := [
Processor activeProcess name: self class name, ' TX'.
[stopped] whileFalse: [self sendOne].
] fork.
]
processOne [
<category: 'receive'>
| msg |
[
msg := demux next.
] on: SystemExceptions.EndOfStream do: [:e |
Transcript
nextPutAll: 'Socket is at an end.'; nl.
self stop.
^ false.
] on: SystemExceptions.FileError do: [:e |
Transcript
nextPutAll: 'FileError on read'; nl.
self stop.
^ false.
].
OsmoDispatcher
dispatchBlock: [rxDispatch dispatch: msg first with: msg second].
]
sendOne [
| msg |
<category: 'send'>
msg := txQueue next.
"Pill of death?"
msg isNil ifTrue: [^false].
socket nextPutAllFlush: msg.
]
send: aMsg [
<category: 'send'>
mux nextPut: aMsg with: self streamId
]
onData: aBlock [
<category: 'input'>
onData := aBlock.
]
onStop: aBlock [
<category: 'input'>
onStop := aBlock.
]
onConnect: aBlock [
<category: 'input'>
onConnect := aBlock.
]
stop [
<category: 'control'>
"Already stopped?"
stopped ifTrue: [^false].
stopped := true.
"Close things down."
socket close.
socket := nil.
txQueue nextPut: nil.
"Inform about the end of stream."
onStop isNil ifFalse: [
OsmoDispatcher
dispatchBlock: [onStop value]].
]
gotIdRequest [
<category: 'connection'>
connected ifTrue: [^true].
connected := true.
onConnect isNil ifFalse: [
OsmoDispatcher
dispatchBlock: [onConnect value]].
]
]
BTSConnectionBase subclass: BTSOmlConnection [
<category: 'BTS-Core'>
<comment: 'I am the OML connection'>
BTSOmlConnection class >> defaultPort [
<category: 'port'>
^ 3002
]
BTSOmlConnection class >> ipaPrototype [
<category: 'internal'>
^ IPAConstants protocolOML
]
streamConnected [
<category: 'initialize'>
rxDispatch
addHandler: self streamId
on: [:msg | self handleOml: msg].
]
handleOml: aMsg [
<category: 'input'>
onData value: aMsg
]
]
BTSConnectionBase subclass: BTSRslConnection [
<category: 'BTS-Core'>
<comment: 'I am the RSL connection'>
BTSRslConnection class >> defaultPort [
<category: 'port'>
^ 3003
]
BTSRslConnection class >> ipaPrototype [
<category: 'internal'>
^ IPAConstants protocolRSL
]
streamConnected [
<category: 'initialize'>
rxDispatch
addHandler: self streamId
on: [:msg | self handleRsl: msg].
]
handleRsl: aMsg [
<category: 'input'>
onData value: aMsg
]
]

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

@ -0,0 +1,74 @@
"
(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/>.
"
OpenBSCTest subclass: TestLU [
<import: OsmoGSM>
createLU [
<category: 'helper'>
| lu lai |
"Create a LU coming from a different network."
lu := GSM48LURequest new.
lu mi imsi: '12345567890'.
lai := lu lai.
lai mcc: 208.
lai mnc: 8.
lai lac: 29701.
^ lu
]
createIdentityResponse: aRequest [
| mi |
<category: 'helper'>
mi := GSM48IdentityResponse new.
"Respond with a IMEI(SV) or IMSI"
aRequest idType isIMSI
ifTrue: [mi imsi: '12345567890']
ifFalse: [mi imei: '000000000000'].
^ mi
]
runLu [
<category: 'test'>
| lchan stop |
"Run a simple LU"
self createAndConnectBTS.
(Delay forSeconds: 2) wait.
lchan := self requireAnyChannel.
lchan sendGSM: self createLU toMessage.
stop := false.
[stop] whileFalse: [ | msg gsm |
msg := lchan nextSapi0Msg.
gsm := GSM48MSG decode: msg readStream.
"Now dispatch messages the boring way"
gsm type = GSM48RRChannelRelease messageType
ifTrue: [stop := true. lchan releaseAllSapis].
gsm type = GSM48IdentityReq messageType
ifTrue: [lchan sendGSM: (self createIdentityResponse: gsm) toMessage].
].
]
]

View File

@ -0,0 +1,172 @@
"
(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/>.
"
FOMMessage subclass: IPAFOMMessage [
| man |
<category: 'BTS-OML'>
<comment: 'I represent the IPA Manufacturer messages.'>
IPAFOMMessage class >> msgType [
<category: 'parsing'>
^ 16r10
]
IPAFOMMessage class >> fieldBaseClass [
<category: 'parsing'>
^ IPAOMLDataField
]
IPAFOMMessage class >> readFrom: aStream [
| placement seq len man dataStream type |
<category: 'parsing'>
"Sanity checking"
(placement := aStream next) = self placementOnly
ifFalse: [^self error: 'Can not deal with fragmented OML'].
(seq := aStream next) = 0
ifFalse: [^self error: 'Can not deal with sequence numbers'].
"Prepare a new buffer"
len := aStream next.
man := aStream next: aStream next.
dataStream := (aStream next: len) readStream.
type := dataStream next.
IPAOMLDataField allSubclassesDo: [:each |
(each canHandle: type) ifTrue: [
^self new
manId: man;
omDataField: (each readFrom: dataStream);
yourself]].
^ self error: 'Can not parse O&M Data field type:', type asString.
]
manId: anId [
<category: 'creation'>
man := anId
]
manId [
<category: 'accessing'>
^ man
]
writeOn: aMsg [
| msg |
<category: 'serialize'>
msg := om_field toMessage asByteArray.
aMsg
putByte: self class msgType;
putByte: self class placementOnly;
putByte: 0;
putByte: msg size;
putByte: man size;
putByteArray: man;
putByteArray: msg.
]
createAck [
<category: 'acking'>
"Try to create an ACK"
^ self class new
manId: self manId;
omDataField: om_field createAck;
yourself
]
]
OMLDataField subclass: IPAOMLDataField [
<category: 'BTS-OML'>
<comment: 'I represent IPA messages. I am just a baseclass '>
IPAOMLDataField class >> canHandle: aType [
<category: 'parsing'>
"Exclude myself from possible parsers"
^ self = IPAOMLDataField
ifTrue: [false]
ifFalse: [super canHandle: aType].
]
]
IPAOMLDataField subclass: IPAOMLRSLConnect [
| streamid port |
<category: 'BTS-OML'>
<comment: 'A request to make a RSL connection'>
IPAOMLRSLConnect class >> attributeType [
<category: 'parsing'>
^ 16rE0
]
IPAOMLRSLConnect class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (TLVDescription newOMLDescription
tag: 16r85; beTV; valueSize: 1;
instVarName: #streamid; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription newOMLDescription
tag: 16r81; beTV; valueSize: 2;
instVarName: #port; parseClass: OMLAttributeData;
yourself);
yourself.
]
streamId [
<category: 'accessing'>
^ streamid
]
streamId: anId [
<category: 'creation'>
streamid := anId
]
port [
<category: 'accessing'>
^ port
]
port: aPort [
<category: 'creation'>
port := aPort
]
createAck [
<category: 'acking'>
^ IPAOMLRSLConnectAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
streamId: self streamId;
port: self port;
yourself.
]
]
IPAOMLRSLConnect subclass: IPAOMLRSLConnectAck [
<category: 'BTS-OML'>
<comment: 'A request to make a RSL connection'>
IPAOMLRSLConnectAck class >> attributeType [
<category: 'parsing'>
^ 16rE1
]
]

File diff suppressed because it is too large Load Diff

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

@ -0,0 +1,418 @@
"
(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/>.
"
"Attempt to have the OMLinit as a imperative routine"
Object subclass: OMLInstanceInit [
| queue omlTarget omlInit |
<category: 'BTS-OML-Tests'>
<comment: 'I am the helper class for powering up a single
instance. I am easily extendable for the different phases.'>
OMLInstanceInit class >> on: anOMLInstance withInit: omlInit withQueue: aQueue [
<category: 'creation'>
^ self new
omlTarget: anOMLInstance;
omlInit: omlInit;
queue: aQueue;
yourself
]
queue: aQueue [
<category: 'creation'>
queue := aQueue
]
omlTarget: aTarget [
<category: 'creation'>
omlTarget := aTarget
]
omlInit: anInit [
<category: 'creation'>
omlInit := anInit
]
waitForSWActivation [
| msg |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLSWActivateRequestAck
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
Transcript nextPutAll: 'SWActivation for '; nextPutAll: omlTarget class name; nl.
omlTarget loadSoftware: msg omDataField swConfiguration.
]
activateSoftware [
| msg ack |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLActivateSoftware
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
omlTarget activateSoftware: msg omDataField swDescription.
ack := msg createAck.
omlInit forwardOML: ack toMessage.
]
waitForAttributes [
<category: 'private'>
"Depending on the object all attributes should be set before the
opstart"
]
waitForOpStart [
| msg ack res |
<category: 'private'>
msg := queue next.
msg omDataField class = OMLOpstart
ifFalse: [^self error: 'Failed to get the Opstart.'].
res := omlTarget opstart.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
"TODO: required by GSM12.21 but problematic with GSM 12.21"
"omlTarget sendStateChanged."
]
start: onActivatedBlock [
"1. Load the software"
self waitForSWActivation.
"2. Activate the software. The stateChanged triggered and activated
report are not the same as with the nanoBTS."
self activateSoftware.
"3. The SM is up launch the BTS"
omlTarget softwareActivated.
onActivatedBlock value.
"4. OpStart or activate requests.."
self waitForAttributes.
self waitForOpStart.
"The below exposes a bug in the OpenBSC OML init. The graphics on page
16 of 12.21 is pretty clear that we should send a chaged state event
report... but sending 'Enabled' again will trigger a new opstart."
"dest sendStateChanged. -- causes the BSC to send OpStart again"
Transcript nextPutAll: 'Opstarted ', omlTarget class name; nl.
]
]
OMLInstanceInit subclass: OMLBTSInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the BTS Instance and deal with attributes'>
waitForAttributes [
| msg res ack |
<category: 'protected'>
msg := queue next.
msg omDataField class = OMLSetBTSAttributes
ifFalse: [self error: 'Failed to get SetBTSAttributes'].
res := omlTarget btsAttributes: msg omDataField.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
]
]
OMLInstanceInit subclass: OMLTrxInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the TRX Instance and deal with attributes'>
]
OMLInstanceInit subclass: OMLRadioCarrierInstanceInit [
<category: 'BTS-OML-Tests'>
<comment: 'I can initialize the TRX Instance and deal with attributes'>
waitForAttributes [
| msg res ack |
<category: 'radio-carrier'>
msg := queue next.
msg omDataField class = OMLSetRadioCarrierAttributes
ifFalse: [self error: 'Failed to get RadioCarrier Attributes'].
res := omlTarget radioCarrierAttributes: msg omDataField.
ack := msg createResponse: res.
omlInit forwardOML: ack toMessage.
]
]
Object subclass: OMLBTSInit [
| sm bts queues |
<category: 'OML-BTS'>
<comment: 'I try to simulate the start-up of a BTS. I am an
attempt to use continuations for writing an imperative init
script. This can be used to tweak it for various failure events. The
execution starts in the the >>#run selector which will spawn the
SiteManager, the SiteManager will spawn the BTS, the BTS will spawn
the RadioCarrier and the BasebandTransceiver and finally the RadioChannels
will be spawned. Then it waits for all init processes to have
finished. The AdminLock is handled out-of-band. Another way to
write this code is to have a loop and a local state machine.'>
OMLBTSInit class >> initWith: aBts [
<category: 'creation'>
^ self new
bts: aBts;
yourself
]
bts: aBts [
<category: 'creation'>
bts := aBts.
sm := aBts siteManager.
]
forwardOML: aMsg [
"It could be filtered here"
bts sendOML: aMsg
]
checkIsFOM: msg [
<category: 'verify'>
msg class = FOMMessage
ifTrue: [^true].
msg class = IPAFOMMessage
ifTrue: [^true].
msg inspect.
^self error: 'Failed to get a (IPA) Formatted O&M message'
]
startRSL: aRsl on: aTrx [
| port |
port := (aRsl port data asByteArray ushortAt: 1) swap16.
bts startRSL: port streamId: aRsl streamId data first on: aTrx.
^ true
]
smInit: aSem [
| smQueue btsProc btsSem init |
"1. Initialize the SM"
smQueue := SharedQueue new.
queues := Dictionary new
at: sm fomKey put: smQueue;
yourself.
sm start.
init := OMLInstanceInit on: sm withInit: self withQueue: smQueue.
"Get the SM into the enabled state"
btsSem := Semaphore new.
init start: [
btsProc := [self btsInit: btsSem] fork.
btsProc name: 'BTS Init process'.
].
btsSem wait.
"Enable the SM now.. OpenBSC will send a Opstart again..."
sm availabilityStatus state: nil.
sm sendStateChanged.
aSem signal.
]
initBtsInstance: bts withQueue: btsQueue [
^ OMLBTSInstanceInit on: bts withInit: self withQueue: btsQueue.
]
btsInit: aSem [
| btsQueue bts init trxSem rcSem |
btsQueue := SharedQueue new.
bts := sm bts.
queues at: bts fomKey put: btsQueue.
"1. Activate the software"
self forwardOML: bts createSwActivateRequest toMessage.
init := self initBtsInstance: bts withQueue: btsQueue.
"Get the SM into the enabled state"
trxSem := Semaphore new.
rcSem := Semaphore new.
init start: [
"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}.
].
].
"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 on: trx [
| trxQueue init msg res ack tss |
trxQueue := SharedQueue new.
queues at: trx fomKey put: trxQueue.
"1. Activate the software"
self forwardOML: trx createSwActivateRequest toMessage.
init := OMLTrxInstanceInit on: trx withInit: self withQueue: trxQueue.
"Get the SM into the enabled state"
init start: [].
"Wait for the RSL Connect"
msg := trxQueue next.
msg omDataField class = IPAOMLRSLConnect
ifFalse: [self error: 'Failed to get the RSL Connect'].
res := self startRSL: msg omDataField on: trx.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
"TODO: there is no proper dependency handling"
"Start the RadioCarrier now"
tss := OrderedCollection new.
1 to: 8 do: [:each | | tsProc tsSem |
tsSem := Semaphore new.
tsProc := [self tsInit: (trx channel: each) with: tsSem] fork.
tsProc name: 'TS(%1) init' % {each}.
tss add: tsSem->tsProc.
].
"Wait for all TSs to be up"
tss do: [:each | each key wait].
trx availabilityStatus state: nil.
trx sendStateChanged.
aSem signal.
]
rcInit: aSem on: rc [
| rcQueue init |
rcQueue := SharedQueue new.
queues at: rc fomKey put: rcQueue.
"1. Activate the software"
self forwardOML: rc createSwActivateRequest toMessage.
init := OMLRadioCarrierInstanceInit on: rc withInit: self withQueue: rcQueue.
"Get the SM into the enabled state"
init start: [].
rc availabilityStatus state: nil.
rc sendStateChanged.
aSem signal.
]
tsInit: aTs with: tsSem [
| tsQueue msg res ack |
<category: 'init'>
tsQueue := SharedQueue new.
queues at: aTs fomKey put: tsQueue.
"1. Initialize the TS no need to activate the software"
aTs operationalState state: OMLOperationalState disabled.
"They are just offline but... OpenBSC has a bug/quirk for the nanoBTS"
aTs availabilityStatus state: OMLAvailabilityStatus dependency.
aTs sendStateChanged.
msg := tsQueue next.
msg omDataField class = OMLSetChannelAttributes
ifFalse: [^self error: 'Failed to get the SetChannelAttributes'].
res := aTs setChannelAttributes: msg omDataField.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
"Opstart it now"
msg := tsQueue next.
msg omDataField class = OMLOpstart
ifFalse: [^self error: 'Failed to get the Opstart.'].
res := aTs opstart.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
aTs availabilityStatus state: nil.
aTs sendStateChanged.
tsSem signal.
]
handleAdminChange: aMsg [
| target res key |
"Handle out of place admin changes"
key := Array
with: aMsg omDataField objectInstance
with: aMsg omDataField objectClass.
target := sm findObject: key.
res := target changeAdminState: aMsg omDataField adminState.
self forwardOML: (aMsg createResponse: res) toMessage.
]
forwardToQueue: aMsg [
| key |
<category: 'forward'>
key := Array
with: aMsg omDataField objectInstance
with: aMsg omDataField objectClass.
(queues at: key) nextPut: aMsg.
]
run [
| smProc sem |
"0. Initialize all queues"
sem := Semaphore new.
smProc := [self smInit: sem] fork.
smProc name: 'SiteManager init'.
"1. dispatch messages"
[
| msg |
msg := bts waitForOMLMsg.
msg isNil ifTrue: [
Transcript nextPutAll: 'OML End of connection'; nl.
^false].
self checkIsFOM: msg.
(msg omDataField class = OMLChangeAdminState)
ifTrue: [self handleAdminChange: msg]
ifFalse: [self forwardToQueue: msg].
sem wouldBlock not
ifTrue: [
"Be lazy and terminate.. on-going OML messages will not
be handled as of now."
Transcript nextPutAll: 'BTS is fully initialized.'; nl.
bts omlUp.
^true]
"Errors should cause an exception and termination"
] repeat.
]
]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,12 @@
ip.access:
After OpStart BTS SiteManager should be disabled/offline but
it is enabled (with no additional availability state)
OpenBSC:
Sending OpStart before the Software Activated Report has been
received. It luckily works.
Sending OpStart as a response to the StateChange Report, e.g.
after OpStart a state changed report should be sent, this is
responded by another OpStart..

View File

@ -0,0 +1,263 @@
"
(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/>.
"
LogicalChannel extend [
sendGSM: aMsg [
<category: '*-OpenBSC-Test'>
self sendGSM: aMsg sapi: 0.
]
sendGSM: aMsg sapi: aSapi [
<category: '*-OpenBSC-Test'>
(self sapiIsEstabliashed: aSapi)
ifTrue: [self sendData: aMsg on: aSapi]
ifFalse: [self establish: aMsg on: aSapi].
]
]
Object subclass: LogicalChannelWrapper [
| sapi0 sapi3 lchan |
<comment: 'I am wrapping a LogicalChannel and provide SAPI
access to it.'>
LogicalChannelWrapper class >> initWith: aLchan [
<category: 'creation'>
^ self new
lchan: aLchan; yourself
]
lchan: aLchan [
<category: 'creation'>
lchan := aLchan.
sapi0 := SharedQueue new.
sapi3 := SharedQueue new.
lchan onDataRequest: [:msg :sapi |
sapi = 0
ifTrue: [sapi0 nextPut: msg].
sapi = 3
ifTrue: [sapi3 nextPut: msg].
].
]
nextSapi0Msg [
<category: 'msg'>
^ sapi0 next
]
nextSapi3Msg [
<category: 'msg'>
^ sapi3 next.
]
sendGSM: aGSM [
<category: 'sending'>
lchan sendGSM: aGSM
]
sendGSM: aGSM sapi: aSapi [
<category: 'sending'>
lchan sendGSM: aGSM sapi: aSapi
]
releaseAllSapis [
<category: 'release'>
Transcript nextPutAll: 'Releasing all SAPIs of the channel'; nl.
(lchan sapiIsEstabliashed: 0)
ifTrue: [lchan releaseSapi: 0].
(lchan sapiIsEstabliashed: 3)
ifTrue: [lchan releaseSapi: 3].
]
onReleaseReqCB: aCb [
<category: 'release'>
lchan onReleaseReqCB: aCb
]
cancel [
<category: 'release'>
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 [
| bts testFailed |
<category: 'OpenBSC-Test'>
<comment: 'I help in dealing with setup and teardown of a test'>
<import: OsmoGSM>
OpenBSCTest class >> initWith: aBTS [
<category: 'creation'>
^ self new
bts: aBTS; yourself.
]
bts: aBTS [
<category: 'creation'>
bts := aBTS
]
createBTS [
^BTS new
]
createAndConnectBTS [
<category: 'bts'>
bts := self createBTS.
bts connect: 'localhost'.
bts waitForBTSReady.
]
createAndConnectBTS: aNr [
<category: 'bts'>
bts := self createBTS.
bts
btsId: aNr;
connect: 'localhost';
waitForBTSReady.
]
bts [
<category: 'accessing'>
^ bts
]
stopBts [
<category: 'bts'>
bts stop.
]
requireChannel: aType random: aMask [
| ra rsl lchan |
<category: 'bts'>
"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: [^self error: 'No LCHAN allocated.'].
^ LogicalChannelWrapper initWith: lchan.
]
requireAnyChannel [
<category: 'bts'>
" Only use four bit for random to work with both necis"
^ self requireChannel: 2r0 random: 2r1111
]
requireEmergencyChannel [
<category: 'bts'>
^ self requireChannel: 2r10100000 random: 2r11111
]
requireTrafficChannel [
<category: 'bts'>
"Originating speech call from dual-rate mobile station when TCH/H
is sufficient and supported by the MS for speech calls and the network"
^ self requireChannel: 2r01000000 random: 2r1111.
]
assert: aBoolean message: aMessage [
<category: 'verifying'>
aBoolean ifTrue: [^self].
Transcript nextPutAll: 'TEST: Failure with ', aMessage; nl.
testFailed := true.
]
deny: aBoolean message: aMessage [
<category: 'verifying'>
self assert: aBoolean not message: aMessage.
]
failed [
<category: 'verifying'>
^ testFailed
]
allocateTmsi: imsi [
| tmsi lchan lu msg |
"Do a LU and get the TMSI."
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send the LU request"
lu := GSM48LURequest new.
lu lai
mcc: 1;
mnc: 1;
lac: 1.
lu mi imsi: imsi.
lchan sendGSM: lu toMessage.
"Now deal with what the NITB wants"
"4.1 Send the IMEI..."
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48IdentityReq)
ifFalse: [^self error: 'Wanted identity request'].
(msg idType isIMEI)
ifFalse: [^self error: 'Wanted IMEI reqest'].
msg := GSM48IdentityResponse new.
msg mi imei: '6666666666666666'.
lchan sendGSM: msg toMessage.
"4.2 LU Accept"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48LUAccept)
ifFalse: [^self error: 'LU failed'].
tmsi := msg mi tmsi.
msg := GSM48TMSIReallocationComplete new.
lchan sendGSM: msg toMessage.
"4.3 MM Information for the time. ignore it"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48MMInformation)
ifFalse: [^self error: 'MM Information'].
"4.4 release.. if we now don't close the LCHAN it will
remain open for a bit. OpenBSC should and will start the
approriate timer soon(tm)"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifFalse: [^self error: 'RR Channel Release'].
"4.5.. be nice... for now and send a disconnect."
lchan releaseAllSapis.
^ tmsi.
]
]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,13 @@
Dispatch the OMLMSG to the 'Procedure'. On the other hand this kills
the procedural init sequence.
Send the stateChanged after Opstart. Update the chain from the radio
channel to the BTS to remove the depndency state...
Allow tests to override the free/release handling.
Tests:
1.) Do not respond to "RR Channel Release", "DEACTIVATE SACCH"...

View File

@ -0,0 +1,664 @@
"
(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/>.
"
TestCase subclass: SiteManagerTest [
<category: 'BTS-OML-Tests'>
testOMLAttributes [
self deny: SiteManagerOML omlAttributes isEmpty
]
testOMLProcedures [
self deny: SiteManagerOML omlProcedures isEmpty
]
testSiteManager [
| site |
site := SiteManagerOML new.
self deny: (site bts basebandTransceiver channel: 1) isNil
]
testFOMAddress [
| sm |
sm := SiteManagerOML new.
self
assert: sm fomInstance bts = 16rFF;
assert: sm fomInstance trx = 16rFF;
assert: sm fomInstance ts = 16rFF.
]
]
TestCase subclass: BTSOMLTest [
<category: 'BTS-OML-Tests'>
testFOMAddress [
| sm |
sm := SiteManagerOML new.
self
assert: sm bts fomInstance bts = 16r0;
assert: sm bts fomInstance trx = 16rFF;
assert: sm bts fomInstance ts = 16rFF.
]
]
TestCase subclass: RadioCarrierOMLTest [
<category: 'BTS-OML-Tests'>
testFOMAddress [
| sm fom |
sm := SiteManagerOML new.
fom := sm bts radioCarrier fomInstance.
self
assert: fom bts = 16r0;
assert: fom trx = 16r0;
assert: fom ts = 16rFF.
]
]
TestCase subclass: BasebandTransceiverOMLTest [
<category: 'BTS-OML-Tests'>
fomState [
<category: 'test-data'>
^ #(16r80 16r80 16r00 16r0D 16r61 16r04 16r00 16r00
16rFF 16r24 16r01 16r07 16r00 16r01 16r07 16r04
16r01)
]
testFOMAddress [
| sm fom |
sm := SiteManagerOML new.
fom := sm bts basebandTransceiver fomInstance.
self
assert: fom bts = 16r0;
assert: fom trx = 16r0;
assert: fom ts = 16rFF.
]
testStateChange [
| sm fom oml |
sm := SiteManagerOML new.
oml := ((sm bts basebandTransceiver)
initializeAttributes;
createStateChange) toMessage asByteArray.
self assert: oml = self fomState asByteArray.
]
]
TestCase subclass: RadioChannelOMLTest [
<category: 'BTS-OML-Tests'>
testFOMAddress [
| sm fom |
sm := SiteManagerOML new.
fom := (sm bts basebandTransceiver channel: 4) fomInstance.
self
assert: fom bts = 16r0;
assert: fom trx = 16r0;
assert: fom ts = 16r3.
]
testChannelNumber [
| sm pchan lchan nr |
"Create the channel"
sm := SiteManagerOML new.
pchan := sm bts basebandTransceiver channel: 2.
pchan createChanSDCCH.
lchan := pchan lchan: 3.
"Now verify the radio channel. Counting starts at 0 there."
nr := lchan channelNumber.
self
assert: nr isSdcch8Acch;
assert: nr subslotNumber = 2;
assert: nr timeslotNumber = 1.
]
]
TestCase subclass: RoundTripTestCase [
<category: 'BTS-OML-Tests'>
parseClass [
<category: 'testing'>
^ self subclassResponsibility
]
convertForClassTest: aMsg [
<category: 'testing'>
^ self subclassResponsibility
]
roundtripTestFor: aSymbol class: aClass [
| msg data want |
<category: 'testing'>
msg := self parseClass parse: (self perform: aSymbol) readStream.
self assert: (self convertForClassTest: msg) = aClass.
data := msg toMessage asByteArray.
want := (self perform: aSymbol) asByteArray.
data = want ifFalse: [
want printNl.
data printNl.
self assert: false.
].
]
]
RoundTripTestCase subclass: OMLMsgTest [
<category: 'BTS-OML-Tests'>
parseClass [
<category: 'testing'>
^ OMLMessageBase
]
convertForClassTest: aMsg [
<category: 'testing'>
^ aMsg omDataField class
]
fomData [
^ #(16r80 16r80 16r00 16r0B 16r61 16r00 16rFF 16rFF
16rFF 16r24 16r01 16r07 16r00 16r01 16r07)
]
swActReqData [
^ #(16r80 16r80 16r00 16r1E 16r0A 16r00 16rFF 16rFF
16rFF 16r16 16r00 16r06 16r01 16r02 16r03 16r04
16r05 16r06 16r41 16r00 16r0D 16r42 16r12 16r00
16r03 16r01 16r02 16r03 16r13 16r00 16r03 16r03
16r04 16r05)
]
swActReqAckData [
^ #(128 128 0 30 11 0 255 255 255 22 0 6 1 2 3 4 5 6
65 0 13 66 18 0 3 1 2 3 19 0 3 3 4 5)
]
activationRequestData [
^ #(128 128 0 18 13 0 255 255 255 66 18 0 3 1 2 3 19 0 3 3 4 5)
]
activationRequestDataAck [
^ #(128 128 0 18 14 0 255 255 255 66 18 0 3 1 2 3 19 0 3 3 4 5)
]
opStartData [
^ #(128 128 0 5 116 0 255 255 255)
]
setBtsAttributesData [
^ #(128 128 0 61 65 1 0 255 255 25 85 91 97 103 109 115 24 6 14
0 2 1 16 51 30 36 36 168 52 33 168 31 63 37 0 1 10 12 10 11
1 42 10 43 3 232 10 128 35 10 8 3 41 9 63 153 0 7 0 241 16 0
1 0 0)
]
adminStateUnlockData [
^ #(128 128 0 7 105 1 0 255 255 4 2)
]
setRadioCarrierAttributesData [
^ #(128 128 0 12 68 2 0 0 255 45 10 5 0 2 3 41 )
]
ipaRslConnectData [
^ #(16 128 0 10 13 99 111 109 46 105 112 97 99 99
101 115 115 0 224 4 0 0 255 133 0 129 11 187)
]
setChannelAttributesData [
^ #(128 128 0 9 71 3 0 0 0 13 5 64 7)
]
getAttributes [
^ #(128 128 0 9 129 4 0 0 255 26 0 1 167)
]
testFomMessage [
| oml |
oml := FOMMessage new
omDataField: (
OMLStateChangedEventReport new
objectClass: FOMMessage objectClassSiteManager;
objectInstance: (FOMObjectInstance new
bts: 16rFF trx: 16rFF ts: 16rFF;
yourself);
operationalState: OMLOperationalState disabledState;
availabilityStatus: OMLAvailabilityStatus notInstalledState;
yourself);
yourself.
self assert: oml toMessage asByteArray = self fomData asByteArray.
]
testSWActivateRequest [
| oml |
oml := FOMMessage new
omDataField: (
OMLSWActivateRequest new
objectClass: FOMMessage objectClassSiteManager;
objectInstance: (FOMObjectInstance new
bts: 16rFF trx: 16rFF ts: 16rFF;
yourself);
hwConfiguration: #(1 2 3 4 5 6);
swConfiguration: (
OMLSWConfiguration new
add: (OMLSWDescription new
fileId: #(1 2 3);
fileVersion: #(3 4 5);
yourself);
yourself);
yourself);
yourself.
self assert: oml toMessage asByteArray = self swActReqData asByteArray
]
testSWActivateRequestAckParsing [
| oml |
oml := OMLMessageBase parse: self swActReqAckData readStream.
]
testActivationRequest [
| oml data |
oml := OMLMessageBase parse: self activationRequestData readStream.
data := oml toMessage asByteArray.
self assert: self activationRequestData asByteArray = data
]
testActivationRequest [
| oml nack |
oml := OMLMessageBase parse: self activationRequestData readStream.
nack := oml createAck.
self assert: nack toMessage asByteArray = self activationRequestDataAck asByteArray.
]
testOpStart [
| oml |
oml := OMLMessageBase parse: self opStartData readStream.
self assert: self opStartData asByteArray = oml toMessage asByteArray
]
testSetBTSAttributes [
| oml nack |
oml := OMLMessageBase parse: self setBtsAttributesData readStream.
self assert: oml omDataField class = OMLSetBTSAttributes.
self assert: oml toMessage asByteArray = self setBtsAttributesData asByteArray.
"Create a nack now"
nack := oml createResponse: false.
self assert: nack omDataField class = OMLSetBTSAttributesNack.
]
testAdmState [
self roundtripTestFor: #adminStateUnlockData class: OMLChangeAdminState.
]
testSetRadioCarrierAttributes [
self roundtripTestFor: #setRadioCarrierAttributesData class: OMLSetRadioCarrierAttributes.
]
testIpaRslConnect [
self roundtripTestFor: #ipaRslConnectData class: IPAOMLRSLConnect.
]
testSetChannelAttributes [
self roundtripTestFor: #setChannelAttributesData class: OMLSetChannelAttributes.
]
testGetAttributes [
self roundtripTestFor: #getAttributes class: OMLGetAttributes.
]
]
TestCase subclass: RSLSmokeTest [
<category: 'BTS-RSL-Test'>
<comment: 'I am a simple smoke test for some of the RSL message support
code. I call the specified categories and test if something is going
wrong with that'>
testDiscriminatorsAreNumbers [
| ran |
RSLMessageBase class methodDictionary keysAndValuesDo: [:key :value |
(key startsWith: 'discriminator') ifTrue: [
ran := true.
self
assert: (RSLMessageBase perform: key) isNumber;
assert: (RSLMessageBase perform: key) highBit <= 8.
]
].
self deny: ran isNil
]
testMessageNamesAreNumbers [
| ran |
RSLMessageBase class methodDictionary keysAndValuesDo: [:key :value |
| handle |
handle := (key startsWith: 'message')
and: [(key startsWith: 'messageType') not].
handle ifTrue: [
ran := true.
self
assert: (RSLMessageBase perform: key) isNumber;
assert: (RSLMessageBase perform: key) highBit <= 8.
]
].
self deny: ran isNil
]
testAttributesAreNumbers [
| ran |
RSLInformationElement class methodDictionary keysAndValuesDo: [:key :value |
(key startsWith: 'attr') ifTrue: [
ran := true.
self
assert: (RSLInformationElement perform: key) isNumber;
assert: (RSLInformationElement perform: key) highBit <= 8.
]
].
self deny: ran isNil
]
testMessageDescriptions [
| ran |
RSLMessageDefinitions class methodDictionary keysAndValuesDo: [:key :value |
| res |
(key endsWith: 'IE') ifFalse: [
ran := true.
res := RSLMessageDefinitions perform: key.
self assert: res class = OrderedCollection.
res do: [:each | self assert: (each isKindOf: TLVDescription)].
].
].
self deny: ran isNil.
]
testInstVarNames [
| ran |
RSLMessageBase allSubclassesDo: [:each |
(RSLMessageBase ignoredBaseClasses includes: each) ifFalse: [
each tlvDescription do: [:attr |
((each indexOfInstVar: attr instVarName) = 0)
ifTrue: [^self error: 'InstVar %1 of %2 not available.' % {attr instVarName. each name.}].
ran := true.
]
]
].
self deny: ran isNil.
]
]
RoundTripTestCase subclass: RSLRoundTripTest [
<comment: 'I test round-trips of RSL messages'>
parseClass [
<category: 'testing'>
^ RSLMessageBase
]
convertForClassTest: aMsg [
<category: 'testing'>
^ aMsg class
]
bcchInformationData [
^ #(12 17 1 128 30 1 39 23 85 6 25 143 148 128 0 0 0 0 0 0 0 0 0 0 0 0 0 229 4 0 43)
]
sacchFillingData1 [
^ #(16 26 30 5 11 0 19 73 6 29 143 148 128 0 0 0 0 0 0 0 0 0 0 0 0 0)
]
sacchFillingData2 [
^ #(16 26 30 6 11 0 12 45 6 30 0 0 0 241 16 0 1 39 255)
]
channelActivationData [
^ #(8 33 1 14 3 0 6 4 0 3 8 0 5 6 100 15 227 41 114 0 4 0 13 7 24 23)
]
immediateAssignmentData [
^ #(12 22 1 144 43 23 45 6 63 3 15 227 41 3 42 20 23 0 43 43 43 43 43
43 43 43 43 43 43)
]
encryptionCommand [
^ #(8 38 1 18 7 9 2 77 103 31 156 22 75 40 0 2 0 11 0 3 6 53 17 )
]
pagingCommandData [
^ #(16r0C 16r15 16r01 16r90 16r0E 16r02 16r0C 16r05 16rF4 16r53
16rD3 16rD3 16r03 16r28 16r02)
]
establishIndicationData [
^ #(16r02 16r06 16r01 16r20 16r02 16r00 16r0B 16r00 16r0F 16r05 16r08
16r00 16r02 16rF8 16r01 16r74 16r05 16r30 16r05 16rF4 16rB5 16r0A
16rB9 16rBB)
]
errorIndicationData [
^#(16r03 16r03 16r01 16r49 16r02 16r03 16r16 16r01 16r01)
]
establishRequestData [
^#(2 4 1 32 2 3)
]
dataRequestData [
^ #(16r03 16r01 16r01 16r20 16r02 16r00 16r0B 16r00 16r03 16r05 16r18 16r02)
]
sacchDeactivateData [
^ #(8 37 1 32)
]
releaseRequestData [
^ #(2 7 1 32 2 0 20 0)
]
modeModifyRequestData [
^ #(8 41 1 10 6 4 0 1 8 17 )
]
ipaCrcxData [
^ #(126 112 1 10 244 17 242 97)
]
ipaCrcxAckData [
^ #(16r7E 16r71 16r01 16r0A 16rF8 16r00 16r27 16rF3 16r0F
16rAE 16rF5 16rC0 16rA8 16r0A 16r4E)
]
ipaDlcxIndData [
^ #(16r7E 16r76 16r01 16r0A 16rF8 16r00 16r27 16rF6 16r1C
16r00 16r00 16r06 16rE4 16r00 16r00 16rD5 16r9C 16r00
16r00 16r07 16r14 16r00 16r00 16rDB 16r6C 16r00 16r00
16r00 16r2A 16r00 16r00 16r00 16r35 16r00 16r00 16r00
16r00 16r1A 16r01 16r0F)
]
ipaMdcxData [
^ #(126 115 1 10 248 0 0 240 0 0 0 0 241 0 0 244 1 242 97)
]
ipaMdcxDataAck [
^ #(16r7E 16r74 16r01 16r0A 16rF8 16r00 16r27)
]
connectionFailureData [
^#(16r08 16r24 16r01 16r49 16r1A 16r01 16r01)
]
testIpaCrcxAck [
self roundtripTestFor: #ipaCrcxAckData class: RSLIPACreateConnectionAck.
]
testIpaCrcx [
self roundtripTestFor: #ipaCrcxData class: RSLIPACreateConnection.
]
testIpaDlcx [
self roundtripTestFor: #ipaDlcxIndData class: RSLIPADeleteConnectionInd.
]
testIpaMdcx [
self roundtripTestFor: #ipaMdcxData class: RSLIPAModifyConnection.
]
testIpaMdcxAck [
self roundtripTestFor: #ipaMdcxDataAck class: RSLIPAModifyConnectionAck.
]
testBCCHInformation [
self roundtripTestFor: #bcchInformationData class: RSLBCCHInformation
]
testSacchFilling [
self roundtripTestFor: #sacchFillingData1 class: RSLSACCHFilling.
self roundtripTestFor: #sacchFillingData2 class: RSLSACCHFilling.
]
testEncryptionCommand [
self roundtripTestFor: #encryptionCommand class: RSLEncryptionCommand.
]
testImmediateAssignment [
| rsl gsm |
self roundtripTestFor: #immediateAssignmentData class: RSLImmediateAssignment.
rsl := RSLMessageBase parse: self immediateAssignmentData readStream.
gsm := OsmoGSM.GSM48MSG decode: (rsl fullL3Info readStream skip: 1; yourself).
self assert: gsm requestReference ra = 3.
]
testChannelActivation [
| rsl |
self roundtripTestFor: #channelActivationData class: RSLChannelActivation.
"Now do some analysis"
rsl := RSLMessageBase parse: self channelActivationData readStream.
"Some simple assertions on the channel number"
self
deny: rsl channelNumber isNil;
assert: rsl channelNumber class = RSLChannelNumber;
assert: rsl channelNumber timeslotNumber = 2r110;
assert: rsl channelNumber cBits = 2r1;
assert: rsl channelNumber isBmAcch;
assert: rsl channelNumber subslotNumber = 0.
]
testEstablishIndication [
self roundtripTestFor: #establishIndicationData class: RSLEstablishIndication.
]
testErrorIndication [
self roundtripTestFor: #errorIndicationData class: RSLErrorIndication.
]
testEstablishRequest [
self roundtripTestFor: #establishRequestData class: RSLEstablishRequest.
]
testDataRequest [
| rsl |
self roundtripTestFor: #dataRequestData class: RSLDataRequest.
rsl := RSLMessageBase parse: self dataRequestData readStream.
self
assert: rsl linkIdentifier data = #(0);
assert: rsl channelNumber isSdcch4Acch;
assert: rsl channelNumber subslotNumber = 0;
assert: rsl channelNumber timeslotNumber = 0;
assert: rsl l3Information data size = 3;
assert: rsl l3Information data = #(16r05 16r18 16r02).
]
testConnectionFailure [
self roundtripTestFor: #connectionFailureData class: RSLConnectionFailure.
]
testSacchDeactivate [
self roundtripTestFor: #sacchDeactivateData class: RSLSacchDeactivate.
]
testReleaseRequestData [
self roundtripTestFor: #releaseRequestData class: RSLReleaseRequest.
]
testPagingCommand [
| msg mi |
self roundtripTestFor: #pagingCommandData class: RSLPagingCommand.
msg := RSLMessageBase parse: self pagingCommandData readStream.
mi := msg msIdenity.
self assert: mi type = OsmoGSM.GSM48IdentityType typeTMSI.
self assert: mi tmsi asByteArray = #(83 211 211 3 ) asByteArray.
]
testModeModify [
self roundtripTestFor: #modeModifyRequestData class: RSLModeModifyRequest.
]
]
TestCase subclass: RSLIETest [
<category: 'BTS-RSL'>
<comment: 'IE testing for RSL'>
testRachTN [
self
assert: RSLChannelNumber ccchRach timeslotNumber = 0;
assert: RSLChannelNumber ccchRach isRacch;
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

@ -0,0 +1,31 @@
<package>
<name>FakeBTS</name>
<namespace>FakeBTS</namespace>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoGSM</prereq>
<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>
<sunit>FakeBTS.SiteManagerTest</sunit>
<sunit>FakeBTS.BTSOMLTest</sunit>
<sunit>FakeBTS.RadioCarrierOMLTest</sunit>
<sunit>FakeBTS.BasebandTransceiverOMLTest</sunit>
<sunit>FakeBTS.RadioChannelOMLTest</sunit>
<sunit>FakeBTS.OMLMsgTest</sunit>
<sunit>FakeBTS.RSLSmokeTest</sunit>
<sunit>FakeBTS.RSLRoundTripTest</sunit>
<sunit>FakeBTS.RSLIETest</sunit>
<sunit>FakeBTS.DualTrxSiteManagerTest</sunit>
<filein>Test.st</filein>
</test>
</package>

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.
]
]

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.
]

View File

@ -0,0 +1 @@
Test Handover

View File

@ -0,0 +1,65 @@
"
(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.OpenBSCTest subclass: IMSIDetach [
<import: OsmoGSM>
startTest [
"1. Connect to the BTS"
self createAndConnectBTS: '1801/0/0'.
self testIMSIDetach.
]
testIMSIDetach [
| lchan detach tmsi |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send a IMSI Detach"
detach := GSM48IMSIDetachInd new.
detach mi tmsi: tmsi.
lchan sendGSM: detach toMessage.
"Wait for the channel to be released.."
[
| msg |
"Read all messages until the end on SAPI=0. Ignore SAPI=3"
"If we send another SAPI=3 Release Indication we get a double
RF Channel Release from the NITB."
[
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifTrue: [lchan releaseAllSapis. ^true]
] on: Exception do: [Transcript nextPutAll: 'GSM decoding error'; nl.].
] repeat.
]
]
Eval [
| test |
test := IMSIDetach new
startTest;
stopBts;
yourself.
]

View File

@ -0,0 +1 @@
Test if OpenBSC is crashing on a IMSI detach

View File

@ -0,0 +1,83 @@
"
(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.OpenBSCTest subclass: LUTest [
<import: OsmoGSM>
startTest [
| lchan lu msg |
"1. Connect to the BTS"
self createAndConnectBTS: '1801/0/0'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send the LU request"
lu := GSM48LURequest new.
lu lai
mcc: 1;
mnc: 1;
lac: 1.
lu mi imsi: '901010000001111'.
lchan sendGSM: lu toMessage.
"Now deal with what the NITB wants"
"4.1 Send the IMEI..."
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48IdentityReq)
ifFalse: [^self error: 'Wanted identity request'].
(msg idType isIMEI)
ifFalse: [^self error: 'Wanted IMEI request'].
msg := GSM48IdentityResponse new.
msg mi imei: '6666666666666666'.
lchan sendGSM: msg toMessage.
"4.2 LU Accept"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48LUAccept)
ifFalse: [^self error: 'LU failed'].
msg := GSM48TMSIReallocationComplete new.
lchan sendGSM: msg toMessage.
"4.3 MM Information for the time. ignore it"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48MMInformation)
ifFalse: [^self error: 'MM Information'].
"4.4 release.. if we now don't close the LCHAN it will
remain open for a bit. OpenBSC should and will start the
approriate timer soon(tm)"
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifFalse: [^self error: 'RR Channel Release'].
"4.5.. be nice... for now and send a disconnect."
lchan releaseAllSapis.
]
]
Eval [
| test |
test := LUTest new
startTest;
stopBts;
yourself.
]

View File

@ -0,0 +1 @@
Perform a LU for a subscriber already in the HLR

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/>.
"
PackageLoader fileInPackage: #FakeBTS.
FakeBTS.OMLBTSInstanceInit subclass: NACKBTSInit [
<import: OsmoGSM>
<comment: 'I will respond with a nack...'>
waitForAttributes [
| msg res nack |
<category: 'protected'>
msg := queue next.
msg omDataField class = OMLSetBTSAttributes
ifFalse: [self error: 'Failed to get SetBTSAttributes'].
nack := msg createResponse: false.
omlInit forwardOML: nack toMessage.
]
]
FakeBTS.OMLBTSInit subclass: NACKInit [
<import: OsmoGSM>
<comment: 'I am an INIT that will nack the BTS Attributes to check
what OpenBSC will do'>
initBtsInstance: aBts withQueue: aQueue [
"Called to initialize the BTS Object"
^ NACKBTSInit on: aBts withInit: self withQueue: aQueue.
]
]
FakeBTS.BTS subclass: NACKBTS [
| oml_gone |
<import: OsmoGSM>
<comment: 'I am a BTS that will NACK the OML init and this should
cause this BTS to be dropped.'>
NACKBTS class >> omlInitClass [
^ NACKInit
]
connect: aHost [
self stop.
rsl := nil.
oml_gone := Semaphore new.
^ super connect: aHost.
]
omlStopped [
oml_gone signal.
]
waitForOMLGone [
"Wait until the OML connection is gone"
oml_gone wait.
]
]
Eval [
| btsAck btsNack test lchan |
"Connect and wait for the BTS to be ready."
btsAck := FakeBTS.BTS new
btsId: '1801/0/0'; connect: 'localhost';
waitForBTSReady; yourself.
"Now connect a NACK bts.."
btsNack := NACKBTS new
btsId: '1802/0/0'; connect: 'localhost';
waitForOMLGone; yourself.
"Verify that the first BTS is still connected"
test := FakeBTS.OpenBSCTest initWith: btsAck.
lchan := test requireAnyChannel.
lchan isNil
ifTrue: [Transcript nextPutAll: 'FAILED TO ALLOCATE A LCHAN'; nl.]
ifFalse: [Transcript nextPutAll: 'Test passed'; nl.].
]

View File

@ -0,0 +1,2 @@
This should test two BTS connecting and the second one should NACK
some OML attributes while the first BTS remains connected.

View File

@ -0,0 +1,147 @@
!
! OpenBSC (0.12.0.18-1a6b8-dirty) configuration saved from vty
!!
password foo
!
log stderr
logging color 1
logging timestamp 0
!
line vty
no login
!
e1_input
e1_line 0 driver ipa
e1_line 0 port 0
network
network country code 1
mobile network code 1
short name OpenBSC
long name OpenBSC
auth policy closed
location updating reject cause 13
encryption a5 0
neci 1
paging any use tch 0
rrlp mode none
mm info 1
handover 0
handover window rxlev averaging 10
handover window rxqual averaging 1
handover window rxlev neighbor averaging 10
handover power budget interval 6
handover power budget hysteresis 3
handover maximum distance 9999
timer t3101 10
timer t3103 0
timer t3105 0
timer t3107 0
timer t3109 0
timer t3111 0
timer t3113 60
timer t3115 0
timer t3117 0
timer t3119 0
timer t3122 0
timer t3141 0
dtx-used 0
subscriber-keep-in-ram 0
bts 0
type nanobts
band DCS1800
cell_identity 0
location_area_code 1
training_sequence_code 7
base_station_id_code 63
ms max power 15
cell reselection hysteresis 4
rxlev access min 0
channel allocator ascending
rach tx integer 9
rach max transmission 7
ip.access unit_id 1801 0
oml ip.access stream_id 255 line 0
neighbor-list mode automatic
gprs mode none
description BTS 1.. not nacked
trx 0
rf_locked 0
arfcn 809
nominal power 23
max_power_red 20
rsl e1 tei 0
timeslot 0
phys_chan_config CCCH+SDCCH4
hopping enabled 0
timeslot 1
phys_chan_config SDCCH8
hopping enabled 0
timeslot 2
phys_chan_config TCH/H
hopping enabled 0
timeslot 3
phys_chan_config TCH/F
hopping enabled 0
timeslot 4
phys_chan_config TCH/F
hopping enabled 0
timeslot 5
phys_chan_config TCH/F
hopping enabled 0
timeslot 6
phys_chan_config TCH/F
hopping enabled 0
timeslot 7
phys_chan_config TCH/F
hopping enabled 0
bts 1
type nanobts
band DCS1800
cell_identity 0
location_area_code 1
training_sequence_code 7
base_station_id_code 63
ms max power 15
cell reselection hysteresis 4
rxlev access min 0
channel allocator ascending
rach tx integer 9
rach max transmission 7
ip.access unit_id 1802 0
oml ip.access stream_id 255 line 0
neighbor-list mode automatic
gprs mode none
description BTS 1.. nacked
trx 0
rf_locked 0
arfcn 809
nominal power 23
max_power_red 20
rsl e1 tei 0
timeslot 0
phys_chan_config CCCH+SDCCH4
hopping enabled 0
timeslot 1
phys_chan_config SDCCH8
hopping enabled 0
timeslot 2
phys_chan_config TCH/F
hopping enabled 0
timeslot 3
phys_chan_config TCH/F
hopping enabled 0
timeslot 4
phys_chan_config TCH/F
hopping enabled 0
timeslot 5
phys_chan_config TCH/F
hopping enabled 0
timeslot 6
phys_chan_config TCH/F
hopping enabled 0
timeslot 7
phys_chan_config TCH/F
hopping enabled 0
mncc-int
default-codec tch-f efr
default-codec tch-h hr

View File

@ -0,0 +1,87 @@
PackageLoader
fileInPackage: #OsmoNetwork;
fileInPackage: #SUnit.
TestCase subclass: NATAuthTest [
| socket demuxer mux queue |
<comment: 'I test the authentication/by-passing of auth on the NAT.'>
<import: Osmo>
connect [
| msg |
socket ifNotNil: [socket close].
socket := Sockets.Socket remote: '127.0.0.1' port: 5000.
queue := SharedQueue new.
demuxer := IPADemuxer initOn: socket.
mux := IPAMuxer initOn: queue.
"ID ACK"
msg := demuxer next.
self assert: msg = (Array with: 254 with: $<6> asString).
"ID Req"
msg := demuxer next.
self assert: msg first = IPAConstants protocolIPA.
self assert: msg second first asInteger = IPAConstants msgIdGet.
"RSIP for MGCP.."
msg := demuxer next.
self assert: msg first = IPAConstants protocolMGCP.
]
run [
self
testByPass;
testShort.
]
verifyNotConnected [
[ | msg |
msg := demuxer next.
self assert: false.
] on: SystemExceptions.EndOfStream do: [^true].
]
testByPass [
| resp |
Transcript nextPutAll: 'Testing by-pass'; nl.
self connect.
"Now construct a response.."
resp := MessageBuffer new
putByte: IPAConstants msgIdResp;
putLen16: 0;
putByte: IPAConstants idtagUnitName;
yourself.
mux nextPut: resp asByteArray with: IPAConstants protocolIPA.
socket nextPutAllFlush: queue next.
self verifyNotConnected.
]
testShort [
| resp |
Transcript nextPutAll: 'Testing short'; nl.
self connect.
"Now construct a short message..."
resp := MessageBuffer new
putByte: IPAConstants msgIdResp;
putLen16: 3;
putByte: IPAConstants idtagUnitName;
putByteArray: 'tes' asByteArray;
yourself.
mux nextPut: resp asByteArray with: IPAConstants protocolIPA.
socket nextPutAllFlush: queue next.
self verifyNotConnected.
]
]
Eval [
| test |
test := NATAuthTest new
run.
]

View File

@ -0,0 +1,9 @@
Some sanity checking with the auth..
1.) Listen on port 5002
$ nc -l 5002
2.) Start the nat with local cfg file
3.) Start the test.

View File

@ -0,0 +1,6 @@
nat
msc port 5002
bsc 0
token test
mgcp
call agent ip 127.0.0.1

View File

@ -0,0 +1 @@
End to End tests for OpenBSC/sysmoBTS

View File

@ -0,0 +1,22 @@
#!/usr/bin/env python
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus
import osmocom.modem
bus = dbus.SystemBus()
modems = osmocom.modem.detect_modems(bus)
print modems

View File

@ -0,0 +1,151 @@
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus
import sim, sms
class Modem(object):
def __init__(self, bus, name):
self.name = name
self.bus = bus
self.modem = dbus.Interface(bus.get_object('org.ofono', name), 'org.ofono.Modem')
def enable(self):
"""
Enable the given modem on the Bus
"""
self.modem.SetProperty("Powered", dbus.Boolean(1), timeout = 120)
def disable(self):
"""
Enable the given modem on the Bus
"""
self.modem.SetProperty("Powered", dbus.Boolean(0), timeout = 120)
def online(self):
"""
Switch-on on the RF Modem
"""
self.modem.SetProperty("Online", dbus.Boolean(1), timeout = 120)
def offline(self):
"""
Switch-off on the RF Modem
"""
self.modem.SetProperty("Online", dbus.Boolean(0), timeout = 120)
def is_enabled(self):
"""
Is the modem online?
"""
return bool(self._get_property('Powered'))
def manufacturer(self):
"""
Who is the owner of the mode?
"""
man = self.modem.GetProperties()
try:
return str(man['Manufacturer'])
except:
return None
def _get_property(self, name):
"""
Internal
"""
return self.modem.GetProperties()[name]
def sim(self):
return sim.Sim(self.bus, self.name)
def sms(self):
return sms.SmsManager(self.bus, self.name)
def register(self):
"""Ask for the module to register"""
network = dbus.Interface(
self.bus.get_object('org.ofono', self.name),
'org.ofono.NetworkRegistration')
network.Register()
def __repr__(self):
return "<Modem('%s')>" % self.name
def get(bus, name):
"""
Find the modem
"""
return Modem(bus, name)
def getmodems(bus):
"""
Find modems...
"""
obj = dbus.Interface(bus.get_object('org.ofono', '/'), 'org.ofono.Manager')
return [Modem(bus, str(x[0])) for x in obj.GetModems()]
def detect_modems(bus, sleep=True, poweroff=True):
"""
Detect the modems that can be used for the test...
"""
modems = getmodems(bus)
# Filter out the phonesim
modems = filter(lambda x: x.name != '/phonesim', modems)
wait = []
on = []
# Enable each modem...
for mod in modems:
if mod.is_enabled():
on.append(mod)
else:
print("Going to enable modem: %s" % mod.name)
mod.enable()
wait.append(mod)
# Now... wait a bit for the modem to do some init
if len(wait) >0 and sleep:
import time
print("I need to sleep some time for the modem to wake up")
time.sleep(20)
for mod in wait:
if mod.is_enabled():
on.append(mod)
# Now filter out the modems without a SIM Card
def modem_vendor(modem):
# Check if the modem vendor was queried
return modem.manufacturer() != None
def sim_present(modem):
return modem.sim().imsi() != None
on = filter(modem_vendor, on)
on = filter(sim_present, on)
# TODO: We could now disable all modems without a SIMcard
for mod in modems:
if mod in on or not poweroff:
continue
print("Modem %s is wihtout SIM card. Powering it down." % mod.name)
mod.disable()
return on

View File

@ -0,0 +1,63 @@
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus, modem, openbsc
class NitbTest(object):
"""
I help with testing NITB/pseudoMSC code. E.g. for call testing..
and SMS..
"""
def __init__(self, host):
self.host = host
self.socket = openbsc.NITBSocket(host)
def setup(self):
# Get the modems.. now check which ones can be used for the
# test with a proper IMSI
self.modems = modem.detect_modems(dbus.SystemBus())
self.avail_modems = []
self.ext2mod = {}
self.mod2ext = {}
for mod in self.modems:
imsi = mod.sim().imsi()
if not self.socket.imsi_present(imsi):
print("Modem('%s') doesn't have a provisioned SIM('%s')" % (mod.name, imsi))
continue
self.avail_modems.append(mod)
ext = self.socket.extension(imsi)
self.ext2mod[ext] = mod
self.mod2ext[mod] = ext
# Now register
try:
mod.register()
except:
print("Registering %s failed. Continuing anyway" % mod)
# TODO: Check if all modems are registered? But this would delay the
# test further. But the modem's SIM card is inside the NITB HLR so it
# should be able to register.
def teardown(self):
pass
def run(self):
self.setup()
self.run_test()
self.teardown()

View File

@ -0,0 +1,61 @@
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
#
# VTY helper code for OpenBSC
#
import socket
class _VTYSocket(object):
def __init__(self, name, host, port):
self.name = name
self.host = host
self.port = port
def connectSendAndWait(self, request):
sck = socket.socket(socket.AF_INET, socket.SOCK_STREAM)
sck.setblocking(1)
sck.connect((self.host, self.port))
sck.recv(4096)
end = '\r\n%s> ' % self.name
# Now send the command
sck.send("%s\r" % request)
res = ""
while True:
data = sck.recv(4096)
res = "%s%s" % (res, data)
if res.endswith(end):
break
sck.close()
return res[len(request) + 2: -len(end)]
class NITBSocket(object):
def __init__(self, host):
self.host = host
def _vty(self):
return _VTYSocket('OpenBSC', self.host, 4242)
def imsi_present(self, imsi):
res = self._vty().connectSendAndWait('show subscriber imsi %s' % imsi)
return not res.startswith('% No subscriber found for imsi ')
def extension(self, imsi):
if not self.imsi_present(imsi):
return None
res = self._vty().connectSendAndWait('show subscriber imsi %s' % imsi)
return res.split('\r\n')[2].split(': ')[1]

View File

@ -0,0 +1,41 @@
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus
class Sim(object):
def __init__(self, bus, path):
self.bus = bus
self.path = path
self.sim = dbus.Interface(bus.get_object('org.ofono', path), 'org.ofono.SimManager')
def imsi(self):
res = self.sim.GetProperties(['SubscriberIdentity'])
try:
return str(res['SubscriberIdentity'])
except:
return None
def present(self):
"""The Wavecom driver is broken and 'detects' a SIM when there is None"""
return self.imsi() != None
def __repr__(self):
return "<Sim(imsi=%s) of '%s'>" % (self.imsi(), self.path)
def get(bus, path):
"""Get the SIM manager"""
return Sim(bus, path)

View File

@ -0,0 +1,63 @@
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus
class Sms(object):
def __init__(self, bus, name):
self.bus = bus
self.name = name
self.sms = dbus.Interface(
bus.get_object('org.ofono', name),
'org.ofono.Message')
def cancel(self):
self.sms.Cancel()
def state(self):
return str(self.sms.GetProperties()['State'])
def __repr__(self):
return "<Sms('%s')>" % self.name
class SmsManager(object):
def __init__(self, bus, name):
self.sms = dbus.Interface(
bus.get_object('org.ofono', name),
'org.ofono.MessageManager')
self.bus = bus
self.name = name
def send_message(self, number, text, delivery_report):
self.sms.SetProperty('UseDeliveryReports', dbus.Boolean(int(delivery_report)))
return self.sms.SendMessage(number, text)
def all_message_names(self):
messages = self.sms.GetMessages()
return map(lambda x: str(x[0]), messages)
def get_message(self, path):
return Sms(self.bus, path)
def registerOnMsgAdded(self, cb):
self.sms.connect_to_signal('MessageAdded', cb)
def registerOnMsgRemoved(self, cb):
self.sms.connect_to_signal('MessageRemoved', cb)
def __repr__(self):
return "<SmsManager for Modem('%s')>" % self.name
def get(bus, name):
return SmsManager(bus, name)

View File

@ -0,0 +1,54 @@
#!/usr/bin/env python
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
import dbus
import dbus.mainloop.glib
import gobject
import time
from osmocom import modem
messages = []
dbus.mainloop.glib.DBusGMainLoop(set_as_default=True)
bus = dbus.SystemBus()
mod = modem.detect_modems(bus, sleep=False, poweroff=False)[0]
print mod.name
sim = mod.sim()
print sim.present()
print sim.imsi()
sms = mod.sms()
sms.send_message('2233', 'BLA', False)
print sms.all_message_names()
for name in sms.all_message_names():
msg = sms.get_message(name)
print msg.state()
print msg
msg.cancel()
#watcher = sms.SmsWatcher(sm)
#for i in range(1, 2000):
# messages.append(sms.sendessage(sm, '39323', 'TEST %d' % i, False))
#time.sleep(2)
#sms.wait_for_sent(messages)
mainloop = gobject.MainLoop()
print dir(mainloop)
mainloop.run()

View File

@ -0,0 +1,67 @@
#!/usr/bin/env python
# Copyright (C) 2012 Holger Hans Peter Freyther
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 2 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 General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program. If not, see <http://www.gnu.org/licenses/>.
# Hi. I am going to send SMS between all available modules and then wait
# for it to complete and verify that all messages arrived and find out
# which one is missing.
from osmocom.nitb_test import NitbTest
class SmsMassTest(NitbTest):
def __init__(self, host, sms_to_send=1000):
NitbTest.__init__(self, host)
self.sms_to_send = sms_to_send
def run_test(self):
"""Run the test"""
self.clear_all_sms()
extensions = self.ext2mod.keys()
for nr in xrange(1, self.sms_to_send):
for modem in self.avail_modems:
self.send_sms(nr, modem, extensions)
# Now wait.... TODO. We could connect to the MessageAdded/Removed
# signal and enter the event loop here...
if len(self.avail_modems) > 0:
print("Queued a lot of SMS... now waiting.")
else:
print("No SMS queued due lack of modems.")
def clear_all_sms(self):
# Clear all SMS so we can easily verify we get SMS..
for modem in self.avail_modems:
sms = modem.sms()
for msg in sms.all_message_names():
try:
sms.get_message(msg).cancel()
except:
print("Deleting SMS('%s') failed. Continuing." % msg)
def send_sms(self, nr, modem, extension_lists):
# Send a SMS to all extensions
sms = modem.sms()
for extension in extension_lists:
# Do not send a SMS to myself (unless this wants to be tested)
if self.ext2mod[extension] == modem:
continue
text = "This is SMS %d from %s to %s" % (nr, self.mod2ext[modem], extension)
sms.send_message(extension, text, False)
if __name__ == "__main__":
SmsMassTest('localhost').run()

View File

@ -0,0 +1 @@
Test that not responding release message still results in a channel release.

View File

@ -0,0 +1,79 @@
"
(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.OpenBSCTest subclass: SACCHTimeout [
<import: OsmoGSM>
SACCHTimeout class >> cpDataRpData [
^ #(
16r09 16r01 16r35 16r01 16r2A 16r07 16r91 16r44
16r77 16r58 16r10 16r06 16r50 16r00 16r2B 16r04
16r04 16r81 16r32 16r24 16r00 16r00 16r80 16r21
16r03 16r41 16r24 16r32 16r40 16r1F 16r41 16r26
16r03 16r94 16r7D 16r56 16rA5 16r20 16r28 16rF2
16rE9 16r2C 16r82 16r82 16rD2 16r22 16r48 16r58
16r64 16r3E 16r9D 16r47 16r10 16rF5 16r09 16rAA
16r4E 16r01) asByteArray.
]
startTest [
"1. Connect to the BTS"
self createAndConnectBTS: '1801/0/0'.
self
testCPTimeoutSacchTimeout.
]
testCPTimeoutSacchTimeout [
| lchan cm tmsi wait |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"Prepare the waiting"
wait := Semaphore new.
lchan onReleaseReqCB: [:sapi |
Transcript nextPutAll: 'Releasing'; nl. wait signal].
"3. Send a CM Service Request "
cm := GSM48CMServiceReq new.
cm mi tmsi: tmsi.
lchan sendGSM: cm toMessage.
"4. CP-DATA/RP-DATA PDU"
lchan sendGSM: self class cpDataRpData sapi: 3.
"Wait for the channel to be released.."
wait wait; wait.
Transcript nextPutAll: 'Channel was released.'; nl.
]
]
Eval [
| test |
test := SACCHTimeout new
startTest;
stopBts;
yourself.
]

View File

@ -0,0 +1,105 @@
"
(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.OpenBSCTest subclass: SMSTest [
<import: OsmoGSM>
SMSTest class >> cpDataRpData [
^ #(
16r09 16r01 16r35 16r01 16r2A 16r07 16r91 16r44
16r77 16r58 16r10 16r06 16r50 16r00 16r2B 16r04
16r04 16r81 16r32 16r24 16r00 16r00 16r80 16r21
16r03 16r41 16r24 16r32 16r40 16r1F 16r41 16r26
16r03 16r94 16r7D 16r56 16rA5 16r20 16r28 16rF2
16rE9 16r2C 16r82 16r82 16rD2 16r22 16r48 16r58
16r64 16r3E 16r9D 16r47 16r10 16rF5 16r09 16rAA
16r4E 16r01) asByteArray.
]
startTest [
"1. Connect to the BTS"
self createAndConnectBTS: '1801/0/0'.
self
testWrongSMSStart;
testCPTimeout.
]
testWrongSMSStart [
| lchan |
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. CP-DATA/RP-DATA PDU"
lchan sendGSM: self class cpDataRpData sapi: 3.
[
| msg |
"Read all messages until the end on SAPI=0. Ignore SAPI=3"
"If we send another SAPI=3 Release Indication we get a double
RF Channel Release from the NITB."
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifTrue: [lchan releaseAllSapis. ^true].
] repeat.
"Current origin/master will be stuck forever here."
]
testCPTimeout [
| lchan cm tmsi |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send a CM Service Request "
cm := GSM48CMServiceReq new.
cm mi tmsi: tmsi.
lchan sendGSM: cm toMessage.
"4. CP-DATA/RP-DATA PDU"
lchan sendGSM: self class cpDataRpData sapi: 3.
"Wait for the channel to be released.."
[
| msg |
"Read all messages until the end on SAPI=0. Ignore SAPI=3"
"If we send another SAPI=3 Release Indication we get a double
RF Channel Release from the NITB."
[
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifTrue: [lchan releaseAllSapis. ^true]
] on: Exception do: [Transcript nextPutAll: 'GSM decoding error'; nl.].
] repeat.
]
]
Eval [
| test |
test := SMSTest new
startTest;
stopBts;
yourself.
]

View File

@ -0,0 +1,4 @@
This attempts to re-produce a CP-ERROR/CP-ACK loop than can be experienced..
This test is not finished! It is meant to be used to re-produce an
issue in the SMC/SMR code of OpenBSC.

View File

@ -0,0 +1,73 @@
"
(C) 2012-2013 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.OpenBSCTest subclass: SMSCPError [
<import: OsmoGSM>
SMSCPError class >> cpError [
^ #(16rC9 16r10 16r51) asByteArray.
]
startTest [
"1. Connect to the BTS"
self createAndConnectBTS: '1801/0/0'.
self
testCpError.
]
testCpError [
| lchan cm tmsi |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send a CM Service Request "
cm := GSM48CMServiceReq new.
cm mi tmsi: tmsi.
lchan sendGSM: cm toMessage.
"4. CP-DATA/RP-DATA PDU"
lchan sendGSM: self class cpError sapi: 3.
"Wait for the channel to be released.."
[
| msg |
"Check what happens as a response to this message now..."
[
msg := GSM48MSG decode: lchan nextSapi0Msg readStream.
(msg isKindOf: GSM48RRChannelRelease)
ifTrue: [lchan releaseAllSapis. ^true].
msg inspect.
] on: Exception do: [Transcript nextPutAll: 'GSM decoding error'; nl.].
] repeat.
]
]
Eval [
| test |
test := SMSCPError new
startTest;
stopBts;
yourself.
]

View File

@ -0,0 +1,76 @@
"
(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.OpenBSCTest subclass: USSDTest [
<import: OsmoGSM>
USSDTest class >> registerMessage [
^#[16r1B 16r3B 16r1C 16r15 16rA1 16r13 16r02
16r01 16r04 16r02 16r01 16r3B 16r30 16r0B
16r04 16r01 16r0F 16r04 16r06 16rAA 16r51
16r0C 16r06 16r1B 16r01 16r7F 16r01 16r00]
]
USSDTest class >> interrogateSS [
^#[16r1B 16r7B 16r1C 16r0D 16rA1 16r0B 16r02
16r01 16r01 16r02 16r01 16r0E 16r30 16r03
16r04 16r01 16r11 16r7F 16r01 16r00]
]
startTest [
"1. Connect to the BTS"
" bts := self createBTS.
bts btsId: '106/0/0'.
bts connect: '192.168.46.1'.
bts waitForBTSReady."
self createAndConnectBTS: '1234/0/0'.
self
testUSSDMessage
]
testUSSDMessage [
| tmsi cm lchan |
tmsi := self allocateTmsi: '901010000001111'.
"2. Get a LCHAN"
lchan := self requireAnyChannel.
"3. Send a CM Service Request "
cm := GSM48CMServiceReq new.
cm mi tmsi: tmsi.
lchan sendGSM: cm toMessage.
"4. USSD messages"
lchan sendGSM: self class interrogateSS sapi: 3.
stdin next.
]
]
Eval [
| test |
test := USSDTest new
startTest;
stopBts;
yourself.
]