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

Merge remote-tracking branch 'osmo-st-openbsc-test/master'

This commit is contained in:
Holger Hans Peter Freyther 2012-10-12 13:21:11 +02:00
commit 2ab7b133a5
13 changed files with 5537 additions and 0 deletions

View File

@ -0,0 +1,12 @@
Eval [
FileStream
fileIn: 'OMLMsg.st';
fileIn: 'IPAOMLMsg.st';
fileIn: 'OML.st';
fileIn: 'OMLInit.st';
fileIn: 'RSLMsg.st';
fileIn: 'BTS.st';
fileIn: 'BTSConnection.st';
fileIn: 'OpenBSCTest.st';
fileIn: 'ExampleTest.st'.
]

View File

@ -0,0 +1,367 @@
"
(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 [
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLSACCHFilling extend [
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
"nothing todo"
]
]
RSLMessageBase extend [
btsChannelDispatch: aBTS [
| ts lchan |
<category: '*-BTS-Core'>
"Generic channel based dispatch."
ts := aBTS trx channel: self channelNumber timeslotNumber + 1.
lchan := ts lchan: self channelNumber subslotNumber + 1.
self btsDispatchOn: aBTS with: lchan.
]
]
RSLDedicatedChannelManagement extend [
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
self btsChannelDispatch: aBTS.
]
]
RSLChannelActivation extend [
btsAllocateChan: aBTS lchan: aChan [
| ack |
<category: '*-BTS-Core'>
Transcript nextPutAll: 'Allocated channel'; nl.
ack := RSLChannelActivationAck new
channelNumber: self channelNumber;
frameNumber: #(23 42) asRSLAttributeData;
yourself.
aBTS sendRSL: ack toMessage.
]
btsNackChan: aBTS lchan: aLchan [
<category: '*-BTS-Core'>
^ self notYetImplemented
]
btsDispatchOn: aBTS 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 btsAllocateChan: aBTS lchan: lchan]
ifFalse: [self btsNackChan: aBTS lchan: lchan].
]
]
RSLRFChannelRelease extend [
btsDispatchOn: aBTS with: lchan [
<category: '*-BTS-Core'>
lchan releaseRequested.
]
]
RSLImmediateAssignment extend [
btsDispatchOn: aBTS [
| 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 := aBTS trx channel: chan_nr timeslotNumber + 1.
lchan := ts lchan: chan_nr subslotNumber + 1.
"Check that the is allocated."
lchan isFree ifTrue: [^self error: 'The lchan should be allocated.'].
aBTS channelAssigned: lchan ra: gsm requestReference ra.
]
]
RSLDataRequest extend [
btsDispatchOn: aBTS with: lchan [
<category: '*-BTS-Core'>
lchan
dataRequest: self l3Information data
sapi: (self linkIdentifier data first bitAnd: 2r111).
]
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
self btsChannelDispatch: aBTS.
]
]
RSLSacchDeactivate extend [
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
Transcript nextPutAll: 'Deactivating SACCH. Not doing anything'; nl.
]
]
RSLReleaseRequest extend [
btsDispatchOn: aBTS with: lchan [
<category: '*-BTS-Core'>
lchan releaseSapiRequest: self linkIdentifier data first.
]
btsDispatchOn: aBTS [
<category: '*-BTS-Core'>
"A sapi has been released."
self btsChannelDispatch: aBTS.
]
]
Object subclass: BTS [
| site_mgr oml rsl oml_queue oml_init connected oml_up ras ras_mutex bts_id |
<category: 'BTS-Core'>
<comment: 'A fake BTS to test the state machine and inject
RSL messages to test a network without RF.'>
connect: anAddress [
<category: 'connect'>
self stop.
rsl := nil.
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 sendRSL: each].
"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.
]
omlUp [
<category: 'oml'>
oml_up signal.
]
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 [
<category: 'rsl'>
"TODO: handle the stream."
rsl isNil ifFalse: [rsl stop].
rsl := BTSRslConnection new
onData: [:each | self handleRsl: each];
onStop: [self rslStopped];
onConnect: [self rslConnected];
btsId: bts_id;
streamId: anId;
yourself.
rsl connect: oml address port: aPort.
]
btsId: aId [
<category: 'bts'>
bts_id := aId.
]
handleRsl: aMsg [
| rsl |
<category: 'rsl'>
[
| rsl |
rsl := RSLMessageBase parse: aMsg asByteArray readStream.
rsl btsDispatchOn: self.
] on: Exception do: [:e |
Transcript nextPutAll: 'RSL Parsing failed with'; nl.
e inspect.
Transcript
nextPutAll: 'With data: ';
nextPutAll: aMsg asByteArray printString;
nl.
]
]
rslStopped [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Stopped'; nl.
]
rslConnected [
<category: 'rsl'>
Transcript nextPutAll: 'RSL Connected'; nl.
"Send anything so rsl will be initialized."
rsl send: #(1 2 3 4 5).
oml_up signal.
]
sendRSL: aMsg [
<category: 'rsl'>
rsl send: aMsg.
]
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 sendRSL: aMsg.
"Wait for a result and just return the out_chan, remove the entry"
(Delay forSeconds: 2) timedWaitOn: sem.
ras_mutex critical: [ras identityRemove: entry ifAbsent: []].
^ out_chan
]
]

View File

@ -0,0 +1,279 @@
"
(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>
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,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 new
tag: 16r85; beTV; valueSize: 1;
instVarName: #streamid; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
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
]
]

View File

@ -0,0 +1,944 @@
"
(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/>.
"
Object subclass: OMLProcedure [
| procName |
<category: 'BTS-OML'>
<comment: 'I represent a OML Procedure by name'>
OMLProcedure class >> name: aName [
<category: 'creation'>
^ self new
procedureName: aName;
yourself
]
procedureName: aName [
<category: 'creation'>
procName := aName
]
procedureName [
^ procName
]
]
Object subclass: OMLManagerBase [
| attributes parent swActivated swLoaded |
<category: 'BTS-OML'>
<comment: 'I am a base class for GSM 12.21'>
OMLManagerBase class >> new [
<category: 'creation'>
^ super basicNew
basicInitialize;
initialize;
yourself
]
basicInitialize [
<category: 'creation'>
]
parent: aFather [
<category: 'internal'>
parent := aFather
]
siteManager [
<category: 'access'>
^ parent siteManager
]
sendStateChanged [
| oml sm |
<category: 'oml'>
"Create the state changed event"
oml := self createStateChange.
"Find the sitemanager"
sm := self siteManager.
sm forwardData: oml toMessage.
]
operationalState [
<category: 'state'>
^ attributes at: 'Operational State' ifAbsent: [nil].
]
availabilityStatus [
<category: 'state'>
^ attributes at: 'Availability Status' ifAbsent: [nil].
]
administrativeState [
<category: 'state'>
^ attributes at: 'Administrative State' ifAbsent: [nil].
]
administrativeState: aState [
<category: 'state'>
attributes at: 'Administrative State' put: aState.
]
createStateChange [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLStateChangedEventReport new
objectClass: self class objectClass;
objectInstance: self fomInstance;
operationalState: self operationalState;
availabilityStatus: self availabilityStatus;
administrativeState: self administrativeState;
yourself);
yourself.
]
createSwActivatedReport [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLSWActivatedReport new
objectClass: self class objectClass;
objectInstance: self fomInstance;
yourself);
yourself
]
createSwActivateRequest [
<category: 'oml'>
^ FOMMessage new
omDataField: (
OMLSWActivateRequest new
objectClass: self class objectClass;
objectInstance: self fomInstance;
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.
]
initializeAttributes [
<category: 'oml'>
attributes := Dictionary new.
self class omlAttributes do: [:each |
attributes at: each attributeName put: each default copy].
]
basicStart [
<category: 'oml'>
swLoaded := false.
swActivated := false.
self
initializeAttributes;
sendStateChanged.
]
basicOpstart [
<category: 'oml'>
self operationalState state: OMLOperationalState enabled.
self availabilityStatus state: nil.
^ true
]
opstart [
^ self basicOpstart
]
loadSoftware: aSWConfiguration [
<category: 'load'>
swLoaded := true.
]
softwareActivated [
| op_state av_state |
(swActivated or: [swLoaded])
ifFalse: [^self error: 'SW not ready'].
"Report the software being activated"
self siteManager forwardData: self createSwActivatedReport toMessage.
"Update the state"
op_state := self operationalState.
op_state state: OMLOperationalState disabled.
av_state := self availabilityStatus.
av_state state: self class defaultActivatedState.
self sendStateChanged.
]
activateSoftware: aSWDescription [
<category: 'load'>
swActivated := true.
]
changeAdminState: aState [
self administrativeState: aState.
^ true
]
fomKey [
<category: 'oml'>
^ Array
with: self fomInstance
with: self class objectClass.
]
]
OMLManagerBase subclass: SiteManagerOML [
| bts onData |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 SiteManager'>
SiteManagerOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassSiteManager
]
SiteManagerOML class >> defaultActivatedState [
^ OMLAvailabilityStatus offline.
]
SiteManagerOML class >> omlAttributes [
<category: 'gsm-12.21'>
"Kill the default as everything inherits OMLAttribute now"
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Site Inputs');
add: (OMLAttribute name: 'Site Outputs');
add: (OMLAttribute name: 'SW Configuration');
yourself.
]
SiteManagerOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Establish TEI');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set Site Outputs');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
bts := BTSOML new
parent: self;
yourself
]
bts [
<category: 'acccessing'>
^ bts
]
onData: aData [
<category: 'creation'>
onData := aData.
]
start [
| fom |
<category: 'oml'>
self basicStart.
self bts start.
"Ask for the software being activated"
fom := self createSwActivateRequest.
self forwardData: fom toMessage.
]
opstart [
<category: 'load'>
(swActivated not or: [swLoaded not])
ifTrue: [^false].
self basicOpstart.
^ true
]
siteManager [
<category: 'accessing'>
^ self
]
forwardData: aMsg [
<category: 'private'>
onData value: aMsg
]
fomInstance [
<category: 'oml'>
^ FOMObjectInstance new
bts: 16rFF trx: 16rFF ts: 16rFF;
yourself
]
findObject: fomKey [
fomKey = self fomKey
ifTrue: [^self].
^ bts findObject: fomKey
]
]
OMLManagerBase subclass: BTSOML [
| radio_carrier baseband attributes |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 BTS'>
BTSOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassBTS
]
BTSOML class >> defaultActivatedState [
^ OMLAvailabilityStatus dependency.
]
BTSOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'BCCH ARFCN');
add: (OMLAttribute name: 'BSIC');
add: (OMLAttribute name: 'BTS Air Timer');
add: (OMLAttribute name: 'CCCH Load Ind. Period');
add: (OMLAttribute name: 'CCCH Load Threshold');
add: (OMLAttribute name: 'Connection Failure Criterion');
add: (OMLAttribute name: 'GSM Time');
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Intave Parameter');
add: (OMLAttribute name: 'Interterference Level Boundaries');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Max Timing Advance');
add: (OMLAttribute name: 'Ny1');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Overload Period');
add: (OMLAttribute name: 'RACH Busy Threshold');
add: (OMLAttribute name: 'RACH Load Averaging Slots');
add: (OMLAttribute name: 'SW Configuration');
add: (OMLAttribute name: 'T200');
yourself.
]
BTSOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Report Procedures');
add: (OMLProcedure name: 'Set BTS Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
radio_carrier := RadioCarrierOML new
parent: self;
yourself.
baseband := BasebandTransceiverOML new
parent: self;
yourself.
]
radioCarrier [
<category: 'accessing'>
^ radio_carrier
]
basebandTransceiver [
<category: 'accessing'>
^ baseband
]
start [
attributes := nil.
self basicStart.
self basebandTransceiver start.
self radioCarrier start.
]
btsAttributes: btsAttributes [
<category: 'oml'>
attributes := btsAttributes.
^ true
]
fomInstance [
<category: 'oml'>
^ parent fomInstance
bts: 16r0;
yourself.
]
findObject: fomKey [
self fomKey = fomKey
ifTrue: [^self].
fomKey second = radio_carrier class objectClass
ifTrue: [^radio_carrier findObject: fomKey].
^baseband findObject: fomKey.
]
]
OMLManagerBase subclass: RadioCarrierOML [
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Radio carrier'>
RadioCarrierOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassRadioCarrier
]
RadioCarrierOML class >> defaultActivatedState [
^ OMLAvailabilityStatus offline.
]
RadioCarrierOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute name: 'ARFCN List');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'Power Class');
add: (OMLAttribute name: 'RF Max Power Reduction');
add: (OMLAttribute name: 'SW Configuration');
yourself
]
RadioCarrierOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set RadioCarrier Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself
]
initialize [
<category: 'creation'>
]
start [
<category: 'oml'>
self basicStart.
]
fomInstance [
^ parent fomInstance
trx: 16r0;
ts: 16rFF;
yourself.
]
radioCarrierAttributes: attributes [
<category: 'oml'>
^ true
]
findObject: fomKey [
self fomKey = fomKey
ifTrue: [^self].
self error: 'Unknown object'.
]
]
OMLManagerBase subclass: BasebandTransceiverOML [
| channels onData |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Baseband Transceiver'>
BasebandTransceiverOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassBasebandTransceiver
]
BasebandTransceiverOML class >> defaultActivatedState [
^ OMLAvailabilityStatus dependency
]
BasebandTransceiverOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'Manufacturer Dependent State');
add: (OMLAttribute name: 'Manufacturer Id');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'SW Configuration');
yourself
]
BasebandTransceiverOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Connect Terrestrial Signalling');
add: (OMLProcedure name: 'Disconnect Terrestrial Signalling');
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
channels := Array new: 8.
(1 to: 8) do: [:each |
channels at: each put: (ChannelOML new
channel: each;
parent: self; yourself).
].
]
channel: aChannel [
<category: 'accessing'>
^ channels at: aChannel.
]
start [
<category: 'oml'>
self basicStart.
channels do: [:each | each start]
]
fomInstance [
<category: 'oml'>
^ parent fomInstance
trx: 16r0;
yourself.
]
findObject: fomKey [
fomKey = self fomKey
ifTrue: [^self].
fomKey second = ChannelOML objectClass
ifFalse: [^self error: 'Unknown objectClass'].
channels do: [:each | | res |
res := each findObject: fomKey.
res isNil ifFalse: [^res]].
^ self error: 'Unknown radio channel object'.
]
onData: aCb [
<category: 'sending'>
onData := aCb.
]
forwardRsl: aMsg [
<category: 'sending'>
onData value: aMsg.
]
]
OMLChannelCombination extend [
performOnChannel: aChannel [
| ch sel |
<category: '*-BTS-OML-ChannelOML'>
ch := (self class channelNames at: comb) asString.
ch at: 1 put: (ch at: 1) asUppercase.
sel := 'create', ch.
aChannel perform: sel asSymbol.
]
]
Object subclass: LogicalChannel [
| number free sapis ts onDataCb onReleaseReqCB |
<category: 'BTS-OML'>
<comment: 'I am a logical that is on the ChannelOML.'>
LogicalChannel class >> initWith: aNumber [
<category: 'creation'>
^ self new
initialize;
number: aNumber;
yourself
]
initialize [
<category: 'creation'>
free := true.
sapis := Dictionary new.
]
ts: aTs [
<category: 'creation'>
ts := aTs
]
number: aNumber [
<category: 'creation'>
number := aNumber
]
isFree [
<category: 'query'>
^ free
]
allocate [
<category: 'channel-allocation'>
self isFree ifFalse: [^false].
free := false.
^ true.
]
release [
<category: 'channel-allocation'>
self isFree ifTrue: [^false].
free := true.
^ true
]
sapiIsEstabliashed: aSapi [
<category: 'sapi'>
^ sapis includesKey: aSapi.
]
sendData: aMsg on: aSapi [
| rsl |
<category: 'sapi'>
(sapis includesKey: aSapi)
ifFalse: [^self error: 'SAPI is not established'].
rsl := RSLDataIndication new
channelNumber: self channelNumber;
linkIdentifier: {aSapi} asRSLAttributeData;
l3Information: aMsg asRSLAttributeData.
ts forwardRsl: rsl toMessage.
]
establish: aMsg on: aSapi [
| rsl |
<category: 'sapi'>
(sapis includesKey: aSapi)
ifTrue: [^self error: 'SAPI is already established.'].
"Remember which side allocated the SAPI."
sapis at: aSapi put: #ms.
"Create the Establish Indication with the message."
rsl := RSLEstablishIndication new
channelNumber: self channelNumber;
linkIdentifier: {aSapi} asRSLAttributeData;
l3Information: aMsg asRSLAttributeData.
ts forwardRsl: rsl toMessage.
]
channelNumber [
| nr mask chan_nr |
<category: 'chan'>
"Initialize"
mask := 0.
nr := ts channelCombination.
1 to: nr highBit - 1 do: [:each |
mask := mask bitAt: each put: 1].
chan_nr := nr bitOr: (number - 1 bitAnd: mask).
chan_nr := chan_nr bitShift: 3.
chan_nr := chan_nr bitOr: ts timeslotNumber - 1.
^ RSLChannelNumber new
data: (ByteArray with: chan_nr);
yourself.
]
releaseRequested [
<category: 'release'>
self isFree
ifTrue: [^self error: 'Lchan was not allocated.'].
"TODO: check if there is a release handler installed."
self defaultRelease.
]
defaultRelease [
| ack |
<category: 'release'>
free := true.
ack := RSLRFChannelReleaseAck new
channelNumber: self channelNumber;
yourself.
ts forwardRsl: ack toMessage.
]
onDataRequest: aBlock [
<category: 'input'>
onDataCb := aBlock.
]
onReleaseReqCB: aBlock [
<category: 'input'>
onReleaseReqCB := aBlock
]
dataRequest: aMsg sapi: aSapi [
<category: 'input'>
onDataCb value: aMsg value: aSapi.
]
releaseSapiRequest: aSapi [
| rsl |
<category: 'input'>
onReleaseReqCB isNil
ifFalse: [onReleaseReqCB value: aSapi].
rsl := RSLReleaseConfirm new
channelNumber: self channelNumber;
linkIdentifier: (ByteArray with: aSapi) asRSLAttributeData;
yourself.
ts forwardRsl: rsl toMessage.
]
releaseSapi: aSapi [
| rsl |
<category: 'release'>
"Remove the key and if no exception is generated, continue"
sapis removeKey: aSapi.
rsl := RSLReleaseIndication new
channelNumber: self channelNumber;
linkIdentifier: (ByteArray with: aSapi) asRSLAttributeData;
yourself.
ts forwardRsl: rsl toMessage.
]
]
OMLManagerBase subclass: ChannelOML [
| chan_nr channels config |
<category: 'BTS-OML'>
<comment: 'I am the GSM 12.21 Channel'>
ChannelOML class >> objectClass [
<category: 'gsm-12.21'>
^ OMLMessageBase objectClassChannel
]
ChannelOML class >> omlAttributes [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLAttribute name: 'Abis Channel');
add: (OMLAttribute
name: 'Administrative State'
default: OMLAdminState lockedState);
add: (OMLAttribute name: 'ARFCN List');
add: (OMLAttribute
name: 'Availability Status'
default: OMLAvailabilityStatus notInstalledState);
add: (OMLAttribute name: 'Channel Conbination');
add: (OMLAttribute name: 'HW Configuration');
add: (OMLAttribute name: 'HSN');
add: (OMLAttribute name: 'MAIO');
add: (OMLAttribute
name: 'Operational State'
default: OMLOperationalState disabledState);
add: (OMLAttribute name: 'SW Configuration');
add: (OMLAttribute name: 'TSC');
yourself
]
ChannelOML class >> omlProcedures [
<category: 'gsm-12.21'>
^ OrderedCollection new
add: (OMLProcedure name: 'Connect Terrestrial Signalling');
add: (OMLProcedure name: 'Disconnect Terrestrial Signalling');
add: (OMLProcedure name: 'Equipment Management');
add: (OMLProcedure name: 'Get Attributes');
add: (OMLProcedure name: 'Measurement Management');
add: (OMLProcedure name: 'Set Channel Attributes');
add: (OMLProcedure name: 'State Management and Event Report');
add: (OMLProcedure name: 'SW Download Management');
add: (OMLProcedure name: 'Test Management');
yourself.
]
initialize [
<category: 'creation'>
]
start [
<category: 'oml'>
self basicStart.
]
channel: aNr [
<category: 'creation'>
chan_nr := aNr.
]
fomInstance [
^ parent fomInstance
ts: chan_nr - 1;
yourself
]
findObject: fomKey [
^ fomKey = self fomKey
ifTrue: [self]
ifFalse: [nil].
]
setChannelAttributes: chanAttr [
attributes at: 'Channel Combination' put: chanAttr channelCombination.
^ true
]
opstart [
super opstart.
(attributes at: 'Channel Combination') performOnChannel: self.
^ true
]
createChannel: aNr[
<category: 'opstart'>
channels at: aNr put:
((LogicalChannel initWith: aNr)
ts: self; yourself)
]
createChanBCCHComb [
<category: 'opstart'>
"In this model we only care about allocatable channels right now.
We don't schedule anything on the BCCH or such."
config := RSLChannelNumber cnSdcch4Acch.
channels := Array new: 4.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanSDCCH [
<category: 'opstart'>
config := RSLChannelNumber cnSdcch8Acch.
channels := Array new: 8.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanTCHH [
<category: 'opstart'>
config := RSLChannelNumber cnLmAcch.
channels := Array new: 2.
1 to: channels size do: [:each |
self createChannel: each]
]
createChanTCHF [
<category: 'opstart'>
config := RSLChannelNumber cnBmAcch.
channels := Array new: 1.
1 to: channels size do: [:each |
self createChannel: each].
]
createChanPDCH [
<category: 'opstart'>
"TODO... PDCH config"
]
lchan: aNr [
<category: 'access'>
^ channels at: aNr
]
forwardRsl: aMsg [
<category: 'sending'>
"Forward it from the TS -> TRX"
^ parent forwardRsl: aMsg
]
channelCombination [
<category: 'configuration'>
^ config
]
timeslotNumber [
<category: 'configuration'>
^ chan_nr
]
]

View File

@ -0,0 +1,409 @@
"
(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 [
| port |
port := (aRsl port data asByteArray ushortAt: 1) swap16.
bts startRSL: port streamId: aRsl streamId data first.
^ 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.
]
btsInit: aSem [
| btsQueue bts init trxProc trxSem rcProc rcSem |
btsQueue := SharedQueue new.
bts := sm bts.
queues at: bts fomKey put: btsQueue.
"1. Activate the software"
self forwardOML: bts createSwActivateRequest toMessage.
init := OMLBTSInstanceInit on: bts withInit: self withQueue: btsQueue.
"Get the SM into the enabled state"
trxSem := Semaphore new.
rcSem := Semaphore new.
init start: [
trxProc := [self trxInit: trxSem] fork.
trxProc name: 'TRX Init process'.
rcProc := [self rcInit: rcSem] fork.
rcProc name: 'Radio-Carrier Init process'.
].
trxSem wait.
rcSem wait.
bts availabilityStatus state: nil.
bts sendStateChanged.
aSem signal.
]
trxInit: aSem [
| trxQueue trx init msg res ack tss |
trxQueue := SharedQueue new.
trx := sm bts basebandTransceiver.
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.
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 [
| rcQueue rc init |
rcQueue := SharedQueue new.
rc := sm bts radioCarrier.
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,169 @@
"
(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'>
]
sendGSM: aGSM [
<category: 'sending'>
lchan sendGSM: aGSM
]
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.
]
]
Object subclass: OpenBSCTest [
| bts testFailed |
<category: 'OpenBSC-Test'>
<comment: 'I help in dealing with setup and teardown of a test'>
OpenBSCTest class >> initWith: aBTS [
<category: 'creation'>
^ self new
bts: aBTS; yourself.
]
bts: aBTS [
<category: 'creation'>
bts := aBTS
]
createAndConnectBTS [
<category: 'bts'>
bts := BTS new.
bts connect: 'localhost'.
bts waitForBTSReady.
]
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.
^ 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
]
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
]
]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,535 @@
"
(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)
]
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 |
oml := OMLMessageBase parse: self setBtsAttributesData readStream.
self assert: oml omDataField class = OMLSetBTSAttributes.
self assert: oml toMessage asByteArray = self setBtsAttributesData asByteArray.
]
testAdmState [
self roundtripTestFor: #adminStateUnlockData class: OMLChangeAdminState.
]
testSetRadioCarrierAttributes [
self roundtripTestFor: #setRadioCarrierAttributesData class: OMLSetRadioCarrierAttributes.
]
testIpaRslConnect [
self roundtripTestFor: #ipaRslConnectData class: IPAOMLRSLConnect.
]
testSetChannelAttributes [
self roundtripTestFor: #setChannelAttributesData class: OMLSetChannelAttributes.
]
]
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)
]
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)
]
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)
]
testBCCHInformation [
self roundtripTestFor: #bcchInformationData class: RSLBCCHInformation
]
testSacchFilling [
self roundtripTestFor: #sacchFillingData1 class: RSLSACCHFilling.
self roundtripTestFor: #sacchFillingData2 class: RSLSACCHFilling.
]
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.
]
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).
]
testSacchDeactivate [
self roundtripTestFor: #sacchDeactivateData class: RSLSacchDeactivate.
]
testReleaseRequestData [
self roundtripTestFor: #releaseRequestData class: RSLReleaseRequest.
]
]
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.
]
]

View File

@ -0,0 +1,28 @@
<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>OMLInit.st</filein>
<filein>RSLMsg.st</filein>
<filein>BTSConnection.st</filein>
<filein>BTS.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>
<filein>Test.st</filein>
</test>
</package>