1
0
Fork 0

control: Add code that makes it more easy to deal interact with OpenBSC

Add a grammar for the OpenBSC control interface and a class that
makes it more easy to connect to a provider.
This commit is contained in:
Holger Hans Peter Freyther 2013-01-03 23:58:04 +01:00
parent 22e3039b8a
commit 45392894da
5 changed files with 499 additions and 0 deletions

86
OsmoAppConnection.st Normal file
View File

@ -0,0 +1,86 @@
"
(C) 2011-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: 'Sockets'.
Object subclass: OsmoAppConnection [
| socket writeQueue demuxer muxer dispatcher ctrlBlock |
<category: 'Osmo-Control'>
<comment: 'I connect to a OpenBSC App on the Control Port and wait for
TRAPS coming from the server and will act on these.'>
onCtrlData: aBlock [
<category: 'ctrl-dispatch'>
ctrlBlock := aBlock
]
handleCTRL: aCtrl [
<category: 'ctrl-dispatch'>
ctrlBlock value: aCtrl.
]
connect: aPort [
| ipa |
<category: 'connect'>
socket ifNotNil: [socket close].
socket := Sockets.Socket remote: '127.0.0.1' port: aPort.
writeQueue := SharedQueue new.
demuxer := IPADemuxer initOn: socket.
muxer := IPAMuxer initOn: writeQueue.
dispatcher := IPADispatcher new.
dispatcher initialize.
dispatcher
addHandler: IPAConstants protocolOsmoCTRL
on: self with: #handleCTRL:.
ipa := IPAProtoHandler new.
ipa registerOn: dispatcher.
ipa muxer: muxer.
]
connect [
<category: 'connect'>
^ self connect: 4250.
]
sendCtrlData: aData [
muxer nextPut: aData with: Osmo.IPAConstants protocolOsmoCTRL.
]
sendOne [
| msg |
<category: 'dispatch'>
msg := writeQueue next.
socket nextPutAllFlush: msg.
]
dispatchOne [
| msg |
<category: 'dispatch'>
msg := demuxer next.
dispatcher dispatch: msg first with: msg second.
]
]

282
OsmoCtrlGrammar.st Normal file
View File

@ -0,0 +1,282 @@
"
(C) 2011-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: 'PetitParser'.
PP.PPCompositeParser subclass: CtrlGrammar [
<category: 'Osmo-Control-Grammar'>
<comment: 'I can parse the control interface'>
start [
<category: 'grammar'>
^ self message
]
message [
<category: 'message'>
^ self trapMessage / self notSupported
]
notSupported [
<category: 'not-supported'>
^ #any asParser plus.
]
trapMessage [
<category: 'trap'>
^ 'TRAP' asParser trim,
self identifier trim,
self variable trim,
#any asParser plus flatten
]
identifier [
<category: 'identifier'>
^ #digit asParser plus flatten
]
variable [
<category: 'variable'>
^ self variablePart plus
]
variablePart [
<category: 'variable'>
^ (#digit asParser plus / #letter asParser / $- asParser / $_ asParser) plus flatten,
$. asParser optional
]
]
Object subclass: CtrlCmd [
| msg |
<category: 'Osmo-Control'>
<comment: 'I am a base class without any functions'>
CtrlCmd class >> with: aMsg [
<category: 'creation'>
^ self new
instVarNamed: #msg put: aMsg;
yourself
]
isTrap [
<category: 'accessing'>
^ false
]
msg [
<category: 'accesing'>
^ msg
]
]
CtrlCmd subclass: CtrlTrap [
<category: 'Osmo-Control'>
<comment: 'I am a trap'>
CtrlTrap class >> isFor: aPath [
<category: 'creation'>
^ self subclassResponsibility
]
CtrlTrap class >> findTrapFor: nodes [
<category: 'creation'>
CtrlTrap allSubclassesDo: [:trap |
(trap isFor: nodes third)
ifTrue: [^trap with: nodes]].
^ CtrlTrap new
]
]
CtrlTrap subclass: CtrlLocationTrap [
| net_nr bsc_nr bts_nr location |
<category: 'Osmo-Control'>
<comment: 'I handle location traps'>
CtrlLocationTrap class >> isFor: aPath [
<category: 'creation'>
^ aPath last first = 'location-state'.
]
CtrlLocationTrap class >> with: aList [
^ self new
net: (aList third at: 2) first;
bsc: (aList third at: 4) first;
bts: (aList third at: 6) first;
location: aList fourth;
yourself
]
net: aStr [
<category: 'private'>
net_nr := aStr asNumber
]
bsc: aStr [
<category: 'private'>
bsc_nr := aStr asNumber
]
bts: aBts [
<category: 'private'>
bts_nr := aBts asNumber
]
location: aLoc [
<category: 'private'>
location := aLoc substrings: $,.
location size = 8 ifFalse: [
^ self error: 'Failed to parse location'.
].
]
net [
<category: 'accessing'>
^ net_nr
]
bsc [
<category: 'accessing'>
^ bsc_nr
]
bts [
^ bts_nr
]
locTimeStamp [
<category: 'accessing'>
^ location at: 1
]
locState [
<category: 'accessing'>
^ location at: 2
]
locLat [
<category: 'accessing'>
^ location at: 3
]
locLon [
<category: 'accessing'>
^ location at: 4
]
locHeight [
<category: 'accessing'>
^ location at: 5
]
trxAvailable [
<category: 'accessing'>
^ (location at: 6) = 'operational'
]
trxAdminLock [
<category: 'accessing'>
^ (location at: 7) = 'locked'
]
rfPolicy [
<category: 'accessing'>
^ location at: 8
]
rfPolicyOn [
<category: 'accessing'>
^ self rfPolicy = 'on'
]
rfPolicyOff [
<category: 'accessing'>
^ self rfPolicy = 'off'
]
rfPolicyGrace [
<category: 'accessing'>
^ self rfPolicy = 'grace'
]
rfPolicyUnknown [
<category: 'accessing'>
^ self rfPolicy = 'unknown'
]
]
CtrlTrap subclass: CtrlCallStatTrap [
| dict |
<category: 'Osmo-Control'>
<comment: 'I can parse the callstats generated by the NAT'>
CtrlCallStatTrap class >> isFor: aPath [
<category: 'creation'>
(aPath at: 1) first = 'net' ifFalse: [^false].
(aPath at: 3) first = 'bsc' ifFalse: [^false].
(aPath at: 5) first = 'call_stats' ifFalse: [^false].
(aPath at: 6) first = 'v2' ifFalse: [^false].
^ true
]
CtrlCallStatTrap class >> with: aMsg [
<category: 'creation'>
^ (super with: aMsg)
extractMessage;
yourself.
]
extractMessage [
| var data |
"Create aliases to avoid the first first second last madness"
var := msg at: 3.
dict := Dictionary new.
dict at: 'nat_id' put: (var at: 2) first.
dict at: 'bsc_id' put: (var at: 4) first.
data := msg at: 4.
data := data substrings: ','.
data do: [:each |
| split |
split := each substrings: '='.
dict at: split first put: split second.
].
]
at: aName [
^ dict at: aName
]
]
CtrlGrammar subclass: CtrlParser [
<category: 'Osmo-Control'>
<comment: 'I parse the tokens from the Ctrl grammar'>
trapMessage [
^ super trapMessage => [:nodes |
CtrlTrap findTrapFor: nodes].
]
notSupported [
^ super notSupported => [:nodes | CtrlCmd with: nodes asString]
]
]

108
OsmoCtrlGrammarTest.st Normal file
View File

@ -0,0 +1,108 @@
"All rights reserved"
PackageLoader
fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: CtrlGrammarTest [
<category: 'Osmo-Control-Test'>
<comment: 'I test some parts of the grammar'>
CtrlGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('CtrlGrammar')
]
parserClass [
<category: 'accessing'>
^ CtrlGrammar
]
testLocationStateTrap [
| data res |
<category: 'accessing'>
data := 'TRAP 0 net.0.bsc.7.bts.0.location-state 1,fix2d,4.860000,53.941111,0.000000,inoperational,unlocked,on'.
res := self parse: data.
]
]
PP.PPCompositeParserTest subclass: CtrlParserTest [
<category: 'Osmo-Control-Test'>
<comment: 'I test some parts of the grammar'>
CtrlParserTest class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('CtrlParser')
]
parserClass [
<category: 'accessing'>
^ CtrlParser
]
testLocationStateTrap [
| data res |
<category: 'accessing'>
data := 'TRAP 0 net.1.bsc.7.bts.6.location-state 1,fix2d,1.000000,2.000000,3.000000,inoperational,unlocked,on'.
res := self parse: data.
self assert: res net = 1.
self assert: res bsc = 7.
self assert: res bts = 6.
self assert: res locTimeStamp = 1 asString.
self assert: res locLat = '1.000000'.
self assert: res locLon = '2.000000'.
self assert: res locHeight = '3.000000'.
self assert: res rfPolicyOn.
self deny: res trxAvailable.
self deny: res trxAdminLock.
]
testResponseeError [
| data res |
data := 'ERROR 386 Command not found'.
res := self parse: data.
self assert: res msg = data.
]
testCallStatIsFor [
| data |
data := #(('net' $. ) ('1' $. ) ('bsc' $. ) ('7' $. ) ('call_stats' $. ) ('v2' nil ) ).
self assert: (CtrlCallStatTrap isFor: data).
]
testCallStat [
| data res |
<category: 'accessing'>
data := 'TRAP 0 net.1.bsc.7.call_stats.v2 mg_ip_addr=213.167.134.139,mg_port=60480,endpoint_ip_addr=127.0.0.1,endpoint_port=33342,nat_pkt_in=208,nat_pkt_out=0,nat_bytes_in=6055,nat_bytes_out=0,nat_jitter=145,nat_pkt_loss=-1,bsc_pkt_in=0,bsc_pkt_out=208,bsc_bytes_in=0,bsc_bytes_out=6055,bsc_jitter=0,bsc_pkt_loss=0,sccp_src_ref=100,sccp_dst_ref=1000'.
res := self parse: data.
self
assert: (res at: 'nat_id') = '1';
assert: (res at: 'bsc_id') = '7';
assert: (res at: 'mg_ip_addr') = '213.167.134.139';
assert: (res at: 'mg_port') = '60480';
assert: (res at: 'endpoint_ip_addr') = '127.0.0.1';
assert: (res at: 'endpoint_port') = '33342';
assert: (res at: 'nat_pkt_in') = '208';
assert: (res at: 'nat_pkt_out') = '0';
assert: (res at: 'nat_bytes_in') = '6055';
assert: (res at: 'nat_bytes_out') = '0';
assert: (res at: 'nat_jitter') = '145';
assert: (res at: 'nat_pkt_loss') = '-1';
assert: (res at: 'bsc_pkt_in') = '0';
assert: (res at: 'bsc_pkt_out') = '208';
assert: (res at: 'bsc_bytes_in') = '0';
assert: (res at: 'bsc_bytes_out') = '6055';
assert: (res at: 'bsc_jitter') = '0';
assert: (res at: 'bsc_pkt_loss') = '0';
assert: (res at: 'sccp_src_ref') = '100';
assert: (res at: 'sccp_dst_ref') = '1000'.
]
]

16
OsmoCtrlLogging.st Normal file
View File

@ -0,0 +1,16 @@
"I represent the logging areas"
PackageLoader
fileInPackage: 'OsmoLogging'.
Osmo.LogArea subclass: LogAreaCTRL [
<category: 'Osmo-Control'>
LogAreaCTRL class >> areaName [ ^ #ctrl ]
LogAreaCTRL class >> areaDescription [ ^ 'Osmo CTRL handling' ]
LogAreaCTRL class >> default [
^ self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]

View File

@ -20,6 +20,10 @@
<filein>LogAreas.st</filein>
<filein>SocketBase.st</filein>
<filein>TLV.st</filein>
<filein>OsmoCtrlLogging.st</filein>
<filein>OsmoCtrlGrammar.st</filein>
<filein>OsmoAppConnection.st</filein>
<test>
<sunit>Osmo.SCCPTests</sunit>
@ -30,9 +34,12 @@
<sunit>Osmo.ISUPGeneratedTest</sunit>
<sunit>Osmo.OsmoUDPSocketTest</sunit>
<sunit>Osmo.TLVDescriptionTest</sunit>
<sunit>Osmo.CtrlGrammarTest</sunit>
<sunit>Osmo.CtrlParserTest</sunit>
<filein>Tests.st</filein>
<filein>ISUPTests.st</filein>
<filein>IPATests.st</filein>
<filein>TLVTests.st</filein>
<filein>OsmoCtrlGrammarTest.st</filein>
</test>
</package>