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

BSCConfig: Add a very simple BSC configuration class

This commit is contained in:
Holger Hans Peter Freyther 2010-12-15 09:57:19 +01:00
parent 5bbbb1e5cf
commit 55becf79db
3 changed files with 146 additions and 0 deletions

95
BSCConfig.st Normal file
View File

@ -0,0 +1,95 @@
"
(C) 2010 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: BSCConfigItem [
| peer token name lac connected |
BSCConfigItem class >> initWith: aPeer name: aName [
^ self new
peer: aPeer; name: aName; lac: -1; connected: false; yourself
]
BSCConfigItem class >> resolveAddress: aPeer [
^ aPeer isString
ifTrue: [Sockets.SocketAddress byName: aPeer]
ifFalse: [aPeer].
]
peer [ <category: 'accessing'> ^ peer ]
peer: aPeer [
<category: 'private'>
peer := self class resolveAddress: aPeer.
]
name [ <category: 'accessing'> ^ name ]
name: aName [
<category: 'private'>
name := aName.
]
lac [ <category: 'accessing'> ^ lac ]
lac: aLac [
<category: 'private'>
lac := aLac.
]
connected [ <category: 'accessing'> ^ connected ]
connected: aState [
<category: 'private'>
connected := aState.
]
]
Object subclass: BSCConfig [
| bscList |
<comment: 'I know the BSCs that can connect to me'>
removeBSC: aPeer [
| peer |
peer := BSCConfigItem resolveAddress: aPeer.
self bscList removeAllSuchThat: [:element | element peer = peer].
]
removeBSCByLac: aLac [
self bscList removeAllSuchThat: [:element | element lac = aLac].
]
addBSC: ip withName: aName andLac: aLac [
| addr bsc |
<category: 'management'>
"Make sure that no one with the same IP or LAC registers"
addr := Sockets.SocketAddress byName: ip.
bsc := BSCConfigItem initWith: addr name: aName.
bsc lac: aLac.
(self bscList anySatisfy: [:each | each peer = addr ])
ifTrue: [
self error: 'The address needs to be unique'.
].
(self bscList anySatisfy: [:each | each lac = aLac])
ifTrue: [
self error: 'The lac needs to be unique'.
].
self bscList add: bsc.
]
bscList [ ^ bscList ifNil: [bscList := OrderedCollection new]]
]

49
Test.st
View File

@ -56,3 +56,52 @@ TestCase subclass: VLRTest [
self assert: sub1 = sub2.
]
]
TestCase subclass: BSCConfigTest [
<comment: 'I will test the BSCConfig'>
testConfigItem [
| item1 item2 addr |
addr := Sockets.SocketAddress byName: '127.0.0.1'.
item1 := BSCConfigItem initWith: '127.0.0.1' name: 'test1'.
item2 := BSCConfigItem initWith: addr name: 'test2'.
self assert: item1 name = 'test1'.
self assert: item1 peer = addr.
self assert: item1 lac = -1.
self assert: item1 connected not.
self assert: item2 name = 'test2'.
self assert: item2 peer = addr.
self assert: item2 lac = -1.
self assert: item2 connected not.
]
testConfig [
| cfg |
"Test that adding stuff again is refused"
cfg := BSCConfig new.
self shouldnt:
[cfg addBSC: '127.0.0.1' withName: 'abc1' andLac: 2311]
raise: Exception description: 'Simply adding it'.
self should:
[cfg addBSC: '127.0.0.1' withName: 'abc2' andLac: 1123]
raise: Exception description: 'Same IP is forbidden'.
self should:
[cfg addBSC: '127.0.0.2' withName: 'abc3' andLac: 2311]
raise: Exception description: 'Different IP same lac'.
self shouldnt:
[cfg addBSC: '127.0.0.2' withName: 'abc4' andLac: 1123]
raise: Exception description: 'Different IP, different lac'.
self assert: cfg bscList size = 2 description: 'Two BSCs should be registered'.
cfg removeBSC: '127.0.0.1'.
self assert: cfg bscList size = 1 description: 'One BSC should be gone'.
cfg removeBSCByLac: 1123.
self assert: cfg bscList size = 0 description: 'All BSCsshould be removed'.
]
]

View File

@ -7,10 +7,12 @@
<filein>Logging.st</filein>
<filein>VLR.st</filein>
<filein>HLR.st</filein>
<filein>BSCConfig.st</filein>
<test>
<sunit>OsmoMSC.HLRTest</sunit>
<sunit>OsmoMSC.VLRTest</sunit>
<sunit>OsmoMSC.BSCConfigTest</sunit>
<filein>Test.st</filein>
</test>
</package>