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

MSC: Introduce classes for HLR/VLR and create some simple tests

This commit is contained in:
Holger Hans Peter Freyther 2010-12-13 10:20:59 +01:00
parent 6e6e2c2bfe
commit 6e70fbbe4a
4 changed files with 202 additions and 0 deletions

55
HLR.st Normal file
View File

@ -0,0 +1,55 @@
"
This is the interface to the local HLR. It consists out of simple
data that will be used inside the HLR.
"
Object subclass: HLRSubscriber [
|imsi msisdn vlrnumber auKey name |
<category: 'osmo-msc'>
<comment: 'I am one subscriber in the HLR'>
imsi [ <category: 'accessing'> ^ imsi ]
msisdn [ <category: 'accessing'> ^ msisdn ]
vlrnumber [ <category: 'accessing'> ^ vlrnumber ]
aukey [ <category: 'accessing'> ^ auKey ]
name [ <category: 'accessing'> ^ name ]
]
Object subclass: HLR [
<category: 'osmo-msc'>
<comment: 'I am a HLR and I can find subscribers'>
findSubscriberByIMSI: aIMSI [
<category: 'accessing'>
^ self subclassResponsibility
]
updateVLRNumber: aIMSI number: aNumber [
^ self subclassResponsibility
]
]
HLR subclass: HLRLocalCollection [
| subs |
<category: 'osmo-msc-simple'>
<comment: 'I am a very simple local HLR'>
findSubscriberByIMSI: aIMSI [
<category: 'accessing'>
self subs do: [:each |
(each imsi = aIMSI)
ifTrue: [^each]].
^ nil
]
addSubscriber: aIMSI [
| sub |
sub := HLRSubscriber new.
sub instVarNamed: #imsi put: aIMSI.
self subs add: sub.
]
subs [<category: 'private'> ^subs ifNil: [subs := OrderedCollection new]]
]

40
Test.st Normal file
View File

@ -0,0 +1,40 @@
PackageLoader fileInPackage: 'SUnit'.
TestCase subclass: HLRTest [
testHLRFind [
| hlr sub |
hlr := HLRLocalCollection new.
hlr addSubscriber: '123456'.
hlr addSubscriber: '345677'.
self assert: (hlr findSubscriberByIMSI: '123456') isNil not.
self assert: (hlr findSubscriberByIMSI: '345677') isNil not.
self assert: (hlr findSubscriberByIMSI: '432432') isNil.
sub := hlr findSubscriberByIMSI: '123456'.
self assert: sub imsi = '123456'.
]
]
HLRResolver subclass: HLRDummyResolver [
insertSubscriber: aIMSI [ ^ true ]
]
TestCase subclass: VLRTest [
testVLRFind [
| vlr sub1 sub2 |
vlr := VLRLocalCollection initWith: HLRDummyResolver new.
self assert: (vlr insertSubscriber: '123456').
sub1 := vlr findSubscriberByIMSI: '123456' ifAbsent: [2342].
self assert: sub1 imsi = '123456'.
self assert: sub1 tmsi isNil.
sub2 := vlr findSubscriberByTMSI: 2342 ifAbsent: [true].
self assert: (sub2 isKindOf: True).
sub1 instVarNamed: #tmsi put: 2342.
sub2 := vlr findSubscriberByTMSI: 2342 ifAbsent: [false].
self assert: sub1 = sub2.
]
]

92
VLR.st Normal file
View File

@ -0,0 +1,92 @@
"
This is the interface to the VLR
"
Object subclass: VLRSubscriber [
|imsi tmsi msisdn lac|
<category: 'osmo-msc'>
<comment: 'I am one subscriber in the VLR'>
imsi [ <category: 'accessing'> ^ imsi ]
tmsi [ <category: 'accessing'> ^ tmsi ]
msisdn [ <category: 'accessing'> ^ msisdn ]
lac [ <category: 'accessing'> ^ lac ]
]
Object subclass: VLR [
<category: 'osmo-msc'>
<comment: 'I hold the active subscribers'>
activeSubscribers [
<category: 'accessing'>
^ self subclassResponsibility
]
activeSubscribersByLAC: aLac [
<category: 'accessing'>
^ self activeSubscribers
reject: [:each | each ~= aLac ].
]
findSubscriber: aMatch ifAbsent: aBlock [
<category: 'private'>
self activeSubscribers do: [:each |
(aMatch value: each)
ifTrue: [^each].
].
^ aBlock value.
]
findSubscriberByIMSI: aIMSI ifAbsent: aBlock [
<category: 'accessing'>
^ self findSubscriber: [:each | each imsi = aIMSI] ifAbsent: aBlock.
]
findSubscriberByTMSI: aTMSI ifAbsent: aBlock [
<category: 'accessing'>
^ self findSubscriber: [:each | each tmsi = aTMSI] ifAbsent: aBlock.
]
insertSubscriber: aIMSI [
^ self subclassResponsibility
]
]
Object subclass: HLRResolver [
insertSubscriber: aIMSI [
^ self subclassResponsibility
]
]
VLR subclass: VLRLocalCollection [
| subs resolver |
VLRLocalCollection class >> initWith: aResolver [
^ self new
instVarNamed: #resolver put: aResolver;
yourself.
]
insertSubscriber: aIMSI [
| hlr sub |
hlr := resolver insertSubscriber: aIMSI.
hlr ifNil: [^false].
sub := self findSubscriberByIMSI: aIMSI
ifAbsent: [ | sub |
sub := VLRSubscriber new
instVarNamed: #imsi put: aIMSI; yourself.
self subs add: sub].
^ true
]
activeSubscribers [
<category: 'accessing'>
^ self subs
]
subs [ <category: 'private'> ^ subs ifNil: [subs := OrderedCollection new]]
]

15
package.xml Normal file
View File

@ -0,0 +1,15 @@
<package>
<name>OsmoMSC</name>
<namespace>OsmoMSC</namespace>
<prereq>OsmoNetwork</prereq>
<prereq>OsmoLogging</prereq>
<filein>VLR.st</filein>
<filein>HLR.st</filein>
<test>
<sunit>OsmoMSC.HLRTest</sunit>
<sunit>OsmoMSC.VLRTest</sunit>
<filein>Test.st</filein>
</test>
</package>