aboutsummaryrefslogtreecommitdiffstats
path: root/osmo
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2013-03-26 14:53:13 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2013-03-26 14:53:13 +0100
commit1a0b690eaa0a549b9954d10371d16bf031da7287 (patch)
tree9b0be2f4614eeac09c99a551c002735eb61ea520 /osmo
parent1deae5d4ccf9bc471f41f0c7550fd4cace30e937 (diff)
Huge internal restructuring of the in sub-directories
Diffstat (limited to 'osmo')
-rw-r--r--osmo/OsmoAppConnection.st83
-rw-r--r--osmo/OsmoCtrlGrammar.st279
-rw-r--r--osmo/OsmoCtrlGrammarTest.st104
-rw-r--r--osmo/OsmoCtrlLogging.st13
-rw-r--r--osmo/OsmoUDPSocket.st116
5 files changed, 595 insertions, 0 deletions
diff --git a/osmo/OsmoAppConnection.st b/osmo/OsmoAppConnection.st
new file mode 100644
index 0000000..aa59214
--- /dev/null
+++ b/osmo/OsmoAppConnection.st
@@ -0,0 +1,83 @@
+"
+ (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/>.
+"
+
+Object subclass: OsmoAppConnection [
+ | socket writeQueue demuxer muxer dispatcher ctrlBlock |
+ <category: 'OsmoNetwork-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: 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.
+ ]
+]
+
diff --git a/osmo/OsmoCtrlGrammar.st b/osmo/OsmoCtrlGrammar.st
new file mode 100644
index 0000000..0f393b7
--- /dev/null
+++ b/osmo/OsmoCtrlGrammar.st
@@ -0,0 +1,279 @@
+"
+ (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 >> 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: '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)]
+ ]
+]
diff --git a/osmo/OsmoCtrlGrammarTest.st b/osmo/OsmoCtrlGrammarTest.st
new file mode 100644
index 0000000..37e6b7f
--- /dev/null
+++ b/osmo/OsmoCtrlGrammarTest.st
@@ -0,0 +1,104 @@
+"All rights reserved"
+
+PP.PPCompositeParserTest subclass: CtrlGrammarTest [
+ <category: 'OsmoNetwork-Control-Tests'>
+ <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: 'OsmoNetwork-Control-Tests'>
+ <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'.
+ ]
+]
diff --git a/osmo/OsmoCtrlLogging.st b/osmo/OsmoCtrlLogging.st
new file mode 100644
index 0000000..907efd9
--- /dev/null
+++ b/osmo/OsmoCtrlLogging.st
@@ -0,0 +1,13 @@
+"I represent the logging areas"
+
+Osmo.LogArea subclass: LogAreaCTRL [
+ <category: 'OsmoNetwork-Control'>
+ LogAreaCTRL class >> areaName [ ^ #ctrl ]
+ LogAreaCTRL class >> areaDescription [ ^ 'Osmo CTRL handling' ]
+ LogAreaCTRL class >> default [
+ ^ self new
+ enabled: true;
+ minLevel: Osmo.LogLevel debug;
+ yourself
+ ]
+]
diff --git a/osmo/OsmoUDPSocket.st b/osmo/OsmoUDPSocket.st
new file mode 100644
index 0000000..7dafddc
--- /dev/null
+++ b/osmo/OsmoUDPSocket.st
@@ -0,0 +1,116 @@
+"
+ (C) 2010-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: OsmoUDPSocket [
+ | socket queue rx tx net_exit name on_data |
+ <category: 'OsmoNetwork-Socket'>
+ <comment: 'I help in sending and dispatching UDP messages. I will
+ start two processes for socket handling.'>
+
+ OsmoUDPSocket class >> new [
+ <category: 'creation'>
+ ^ super new
+ initialize;
+ yourself
+ ]
+
+ initialize [
+ <category: 'creation'>
+ queue := SharedQueue new.
+ net_exit := Semaphore new.
+ ]
+
+ name: aName [
+ <category: 'creation'>
+ name := aName
+ ]
+
+ onData: aBlock [
+ <category: 'creation'>
+ on_data := aBlock
+ ]
+
+ start: aSocket [
+ <category: 'creation'>
+ socket := aSocket.
+
+ "Receive datagrams from the socket..."
+ rx := self startRXProcess.
+
+ "Send data to the MGWs"
+ tx := [
+ [Processor activeProcess name: name, ' TX'.
+ self runTXProcess] ensure: [net_exit signal]] fork.
+ ]
+
+ startRXProcess [
+ ^ [[Processor activeProcess name: name, ' RX'.
+ self runRXProcess] ensure: [net_exit signal]] fork.
+ ]
+
+ runRXProcess [
+ <category: 'processing'>
+
+ [ | data |
+ socket ensureReadable.
+ socket isOpen ifFalse: [
+ ^self logNotice: name, ' socket closed.' area: #core].
+
+ data := socket next.
+ on_data value: data.
+ ] repeat.
+ ]
+
+ runTXProcess [
+ <category: 'processing'>
+
+ [ | data |
+ data := queue next.
+ data = nil ifTrue: [
+ ^self logNotice: name, ' TX asked to quit.' area: #core].
+
+ socket nextPut: data.
+ ] repeat.
+ ]
+
+ stop [
+ <category: 'processing'>
+
+ socket ifNil: [^self].
+
+ "Close"
+ socket close.
+ queue nextPut: nil.
+
+ "Wait for the process to exit"
+ self logNotice: name, ' waiting for IO handlers to exit.' area: #core.
+ net_exit
+ wait;
+ wait.
+
+ "Forget things"
+ socket := nil.
+ tx := nil.
+ rx := nil.
+ ]
+
+ queueData: aData [
+ <category: 'sending'>
+ queue nextPut: aData
+ ]
+]