smalltalk
/
osmo-st-all
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-all/osmo-st-network/osmo/OsmoCtrlGrammar.st

284 lines
6.2 KiB
Smalltalk

"
(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/>.
"
PP.PPCompositeParser subclass: CtrlGrammar [
<category: 'OsmoNetwork-Control'>
<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: 'OsmoNetwork-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: 'OsmoNetwork-Control'>
<comment: 'I am a trap'>
CtrlTrap class >> isFor: aPath [
<category: 'creation'>
^ self subclassResponsibility
]
CtrlTrap class >> isFor: aPath value: aValue [
^self isFor: aPath
]
CtrlTrap class >> findTrapFor: nodes [
<category: 'creation'>
CtrlTrap allSubclassesDo: [:trap |
(trap isFor: nodes third value: nodes fourth)
ifTrue: [^trap with: nodes]].
^ CtrlTrap new
]
]
CtrlTrap subclass: CtrlLocationTrap [
| net_nr bsc_nr bts_nr location |
<category: 'OsmoNetwork-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: 'OsmoNetwork-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: 'OsmoNetwork-Control'>
<comment: 'I parse the tokens from the Ctrl grammar'>
trapMessage [
^ super trapMessage => [:nodes |
CtrlTrap findTrapFor: nodes].
]
notSupported [
^ super notSupported => [:nodes | CtrlCmd with: (String withAll: nodes)]
]
]