1
0
Fork 0

oml: New approach to the init. We will have separate processes

We start with a SM process, that will spawn the BTS process
which will spawn... communication will occur through queues,
dispatching will happen through the OML queue.
This commit is contained in:
Holger Hans Peter Freyther 2012-08-10 17:03:23 +02:00
parent 3cda1acc92
commit dfa26b01fc
4 changed files with 192 additions and 18 deletions

View File

@ -88,6 +88,11 @@ Object subclass: OMLManagerBase [
^ attributes at: 'Availability Status' ifAbsent: [nil].
]
administrativeState [
<category: 'state'>
^ attributes at: 'Administrative State' ifAbsent: [nil].
]
createStateChange [
<category: 'oml'>
@ -98,8 +103,7 @@ Object subclass: OMLManagerBase [
objectInstance: self fomInstance;
operationalState: self operationalState;
availabilityStatus: self availabilityStatus;
administrativeState:
(attributes at: 'Administrative State' ifAbsent: [nil]);
administrativeState: self administrativeState;
yourself);
yourself.
]
@ -150,6 +154,16 @@ Object subclass: OMLManagerBase [
initializeAttributes;
sendStateChanged.
]
basicOpstart [
<category: 'oml'>
self operationalState state: OMLOperationalState enabled.
self availabilityStatus state: nil.
]
opstart [
^ self basicOpstart
]
]
OMLManagerBase subclass: SiteManagerOML [
@ -254,6 +268,15 @@ OMLManagerBase subclass: SiteManagerOML [
swActivated := true.
]
opstart [
<category: 'load'>
(swActivated not or: [swLoaded not])
ifTrue: [^false].
self basicOpstart.
^ true
]
siteManager [
<category: 'accessing'>
^ self
@ -270,6 +293,12 @@ OMLManagerBase subclass: SiteManagerOML [
bts: 16rFF trx: 16rFF ts: 16rFF;
yourself
]
findObject: anInstance [
^ anInstance = self fomInstance
ifTrue: [self]
ifFalse: [bts findObject: anInstance].
]
]
OMLManagerBase subclass: BTSOML [

View File

@ -19,7 +19,7 @@
"Attempt to have the OMLinit as a imperative routine"
Object subclass: OMLBTSInit [
| sm bts |
| sm bts queues smStarted |
<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
@ -45,15 +45,34 @@ Object subclass: OMLBTSInit [
bts sendOML: aMsg
]
run [
| msg ack |
checkIsFOM: msg [
msg class = FOMMessage
ifFalse: [msg inspect. self error: 'Failed to get a Formatted O&M message'].
]
btsInit [
| btsQueue bts |
btsQueue := SharedQueue new.
bts := sm bts.
queues at: bts fomInstance put: btsQueue.
"1. Activate the software"
self forwardOML: bts createSwActivateRequest toMessage.
]
smInit [
| smQueue msg ack res dest btsProc |
"1. Initialize the SM"
smQueue := SharedQueue new.
queues := Dictionary new
at: sm fomInstance put: smQueue;
yourself.
smStarted signal.
sm start.
"2. Load the software"
msg := bts waitForOMLMsg.
msg class = FOMMessage
ifFalse: [self error: 'Failed to get a Formatted O&M message'].
msg := smQueue next.
msg omDataField class = OMLSWActivateRequestAck
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
Transcript nextPutAll: 'We were asked to activate something'; nl.
@ -61,21 +80,55 @@ Object subclass: OMLBTSInit [
"3. Activate the software. The stateChanged triggered and activated
report are not the same as with the nanoBTS."
msg := bts waitForOMLMsg.
msg class = FOMMessage
ifFalse: [self error: 'Failed to get a Formatted O&M message'].
msg := smQueue next.
msg omDataField class = OMLActivateSoftware
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
sm activateSoftware: msg omDataField swDescription.
ack := msg createAck.
self forwardOML: ack toMessage.
"4. The SM has booted up, ask to activate the software"
"4. The SM is up launch the BTS"
sm softwareActivated.
self forwardOML: sm bts createSwActivateRequest toMessage.
btsProc := [self btsInit] fork.
btsProc name: 'BTS Init process'.
"5. OpStart or activate requests.."
msg := bts waitForOMLMsg.
msg inspect.
msg := smQueue next.
msg omDataField class = OMLOpstart
ifFalse: [self error: 'Failed to get the SW Activate Request ACK'].
dest := sm findObject: msg omDataField objectInstance.
res := dest opstart.
ack := msg createResponse: res.
self forwardOML: ack toMessage.
"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"
]
run [
| smProc |
"0. Initialize all queues"
smStarted := Semaphore new.
smProc := [self smInit] fork.
smProc name: 'SiteManager init'.
smStarted wait.
"1. dispatch messages"
[
| msg |
msg := bts waitForOMLMsg.
msg isNil ifTrue: [
Transcript nextPutAll: 'OML End of connection'; nl.
^false].
self checkIsFOM: msg.
(queues at: msg omDataField objectInstance)
nextPut: msg.
"Errors should cause an exception and termination"
] repeat.
]
]

View File

@ -77,11 +77,29 @@ Object subclass: FOMObjectInstance [
]
writeOn: aMsg [
<category: 'serialize'>
aMsg
putByte: bts;
putByte: trx;
putByte: ts.
]
= anInstance [
<category: 'testing'>
bts = anInstance bts
ifFalse: [^false].
trx = anInstance trx
ifFalse: [^false].
ts = anInstance ts
ifFalse: [^false].
^ true
]
hash [
<category: 'testing'>
^ ((bts bitShift: 16) + (trx bitShift: 8) + ts) hash
]
]
Object subclass: OMLAttribute [
@ -305,9 +323,13 @@ OMLAttribute subclass: OMLAvailabilityStatus [
writeOn: aMsg [
<category: 'serialize'>
aMsg
putLen16: 1;
putByte: state
state isNil
ifTrue: [
aMsg putLen16: 0]
ifFalse: [
aMsg
putLen16: 1;
putByte: state].
]
]
@ -576,6 +598,21 @@ Object subclass: OMLMessageBase [
<category: 'message-type'>
^ 16r0F
]
msgOpstart [
<category: 'message-type'>
^ 16r74
]
msgOpstartAck [
<category: 'message-type'>
^ 16r75
]
msgOpstartNack [
<category: 'message-type'>
^ 16r76
]
]
OMLMessageBase class >> parse: aStream [
@ -658,6 +695,18 @@ OMLMessageBase subclass: FOMMessage [
omDataField: om_field createAck;
yourself
]
createNack [
<category: 'acking'>
^ self notImplementedYet
]
createResponse: aResponse [
<category: 'acking'>
^ aResponse
ifTrue: [self createAck]
ifFalse: [self createNack].
]
]
Object subclass: OMLDataField [
@ -920,3 +969,36 @@ OMLDataField subclass: OMLSWActivatedReport [
^ #()
]
]
OMLDataField subclass: OMLOpstart [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.9.2'>
OMLOpstart class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgOpstart
]
OMLOpstart class >> tlvDescription [
<category: 'parsing'>
^ #()
]
createAck [
<category: 'acking'>
^ OMLOpstartAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
yourself
]
]
OMLOpstart subclass: OMLOpstartAck [
<category: 'BTS-OML'>
<comment: 'I construct a GSM 12.21 O&M Data field as of 8.9.2'>
OMLOpstartAck class >> attributeType [
<category: 'parsing'>
^ FOMMessage msgOpstartAck
]
]

View File

@ -144,6 +144,10 @@ TestCase subclass: OMLMsgTest [
^ #(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)
]
testFomMessage [
| oml |
@ -203,6 +207,12 @@ TestCase subclass: OMLMsgTest [
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
]
]
TestCase subclass: TLVDescriptionTest [