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

test: Splity tests into file per class

This commit is contained in:
Holger Hans Peter Freyther 2014-03-13 12:38:59 +01:00
parent 69ca1cbe52
commit b02113d070
15 changed files with 479 additions and 283 deletions

View File

@ -31,7 +31,18 @@
<sunit>OsmoMSC.BSCIPAConnectionTest</sunit>
<sunit>OsmoMSC.AuthTestNull</sunit>
<sunit>OsmoMSC.AuthTestIdentity</sunit>
<filein>tests/Test.st</filein>
<filein>tests/AuthTest.st</filein>
<filein>tests/HLRDummyResolver.st</filein>
<filein>tests/BSCConfigTest.st</filein>
<filein>tests/BSCIPAConnectionTest.st</filein>
<filein>tests/BSCListenerTest.st</filein>
<filein>tests/HLRTest.st</filein>
<filein>tests/MSCBSCConnectionHandlerTest.st</filein>
<filein>tests/VLRTest.st</filein>
<filein>tests/AuthTestIdentity.st</filein>
<filein>tests/AuthTestNull.st</filein>
<filein>tests/GSMProcessorMockBase.st</filein>
<filein>tests/GSMProcessorMockForAuthCheat.st</filein>
<filein>tests/GSMProcessorMockForAuthIMSI.st</filein>
<filein>tests/GSMProcessorMockForAuthTimeout.st</filein>
</test>
</package>

View File

@ -16,110 +16,6 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
TestCase subclass: AuthTestNull [
<category: 'OsmoMSC-Tests'>
<comment: 'I smoke-test the null authenticator and that it
fires an accept callback right away.'>
testImmediateAccept [
| auth accepted |
auth := GSMNullAuthenticator new
onAccept: [:a| self assert: a = auth. accepted := true];
onReject: [:a| self shouldNotImplement];
yourself.
auth start: OsmoGSM.GSM48CMServiceReq new.
self assert: accepted.
]
testWrongInitialMessage [
| auth rejected wait |
Transcript nextPutAll: 'Going to send an initial message'; nl.
wait := Semaphore new.
auth := GSMNullAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: nil;
start: OsmoGSM.GSM48IdentityReq new.
wait wait.
self assert: rejected.
]
]
Object subclass: GSMProcessorMockBase [
| auth dict |
<category: 'OsmoMSC-Tests'>
GSMProcessorMockBase class >> initWith: anAuth [
^ self new
instVarNamed: #auth put: anAuth;
instVarNamed: #dict put: Dictionary new;
yourself.
]
addInfo: aName value: aValue [
dict at: aName put: aValue.
]
getInfo: aName [
^ dict at: aName
]
srcRef [
^ 1
]
takeLocks: aBlock [
aBlock value
]
]
GSMProcessorMockBase subclass: GSMProcessorMockForAuthCheat [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imei: '234324234234'.
auth onData: msg.]
]
]
GSMProcessorMockBase subclass: GSMProcessorMockForAuthIMSI [
<category: 'OsmoMSC-Tests'>
usedIMSI [
^ '234324234234'
]
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imsi: self usedIMSI.
auth onData: msg.]
]
]
GSMProcessorMockBase subclass: GSMProcessorMockForAuthTimeout [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Do nothing"
]
]
TestCase subclass: AuthTestIdentity [
<category: 'OsmoMSC-Tests'>
<comment: 'I test various aspects of the IMSI requestor.'>

51
tests/AuthTestNull.st Normal file
View File

@ -0,0 +1,51 @@
"
(C) 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/>.
"
TestCase subclass: AuthTestNull [
<category: 'OsmoMSC-Tests'>
<comment: 'I smoke-test the null authenticator and that it
fires an accept callback right away.'>
testImmediateAccept [
| auth accepted |
auth := GSMNullAuthenticator new
onAccept: [:a| self assert: a = auth. accepted := true];
onReject: [:a| self shouldNotImplement];
yourself.
auth start: OsmoGSM.GSM48CMServiceReq new.
self assert: accepted.
]
testWrongInitialMessage [
| auth rejected wait |
Transcript nextPutAll: 'Going to send an initial message'; nl.
wait := Semaphore new.
auth := GSMNullAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: nil;
start: OsmoGSM.GSM48IdentityReq new.
wait wait.
self assert: rejected.
]
]

67
tests/BSCConfigTest.st Normal file
View File

@ -0,0 +1,67 @@
"
(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/>.
"
TestCase subclass: BSCConfigTest [
<category: 'OsmoMSC-Tests'>
<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 deny: item1 connected.
self assert: item2 name = 'test2'.
self assert: item2 peer = addr.
self assert: item2 lac = -1.
self deny: item2 connected.
]
testConfig [
| cfg |
"Test that adding stuff again is refused"
cfg := BSCConfig new.
self shouldnt:
[cfg addBSC: '127.0.0.1' withName: 'abc1' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Simply adding it'.
self should:
[cfg addBSC: '127.0.0.1' withName: 'abc2' andLac: 1123 sendOsmoRSIP: false]
raise: Exception description: 'Same IP is forbidden'.
self should:
[cfg addBSC: '127.0.0.2' withName: 'abc3' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Different IP same lac'.
self shouldnt:
[cfg addBSC: '127.0.0.2' withName: 'abc4' andLac: 1123 sendOsmoRSIP: false]
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

@ -0,0 +1,30 @@
"
(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/>.
"
TestCase subclass: BSCIPAConnectionTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I just do some simple smoke testing here'>
testSmoke [
| ipa |
ipa := BSCIPAConnection
createOn: 'hi' writeStream
withConfig: (BSCConfigItem initWith: '0.0.0.0' name: 'foo')
msc: nil.
]
]

47
tests/BSCListenerTest.st Normal file
View File

@ -0,0 +1,47 @@
"
(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/>.
"
TestCase subclass: BSCListenerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'Test some basic socket functionality'>
testListenAndStop [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
'Will attempt to stop the connection' printNl.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
"Test that it will work again"
'Will attempt to stop the connection2' printNl.
listener start.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
]
testListenOnDeadSocket [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
listener stop.
res := listener serve.
self deny: res.
]
]

View File

@ -0,0 +1,45 @@
"
(C) 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: GSMProcessorMockBase [
| auth dict |
<category: 'OsmoMSC-Tests'>
GSMProcessorMockBase class >> initWith: anAuth [
^ self new
instVarNamed: #auth put: anAuth;
instVarNamed: #dict put: Dictionary new;
yourself.
]
addInfo: aName value: aValue [
dict at: aName put: aValue.
]
getInfo: aName [
^ dict at: aName
]
srcRef [
^ 1
]
takeLocks: aBlock [
aBlock value
]
]

View File

@ -0,0 +1,32 @@
"
(C) 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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthCheat [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imei: '234324234234'.
auth onData: msg.]
]
]

View File

@ -0,0 +1,36 @@
"
(C) 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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthIMSI [
<category: 'OsmoMSC-Tests'>
usedIMSI [
^ '234324234234'
]
nextPutData: aData [
"Ignore the data for now. Should be a identity request"
OsmoDispatcher dispatchBlock: [
| msg |
"Reply with a wrong identity response"
msg := OsmoGSM.GSM48IdentityResponse new.
msg mi imsi: self usedIMSI.
auth onData: msg.]
]
]

View File

@ -0,0 +1,25 @@
"
(C) 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/>.
"
GSMProcessorMockBase subclass: GSMProcessorMockForAuthTimeout [
<category: 'OsmoMSC-Tests'>
nextPutData: aData [
"Do nothing"
]
]

23
tests/HLRDummyResolver.st Normal file
View File

@ -0,0 +1,23 @@
"
(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/>.
"
HLRResolver subclass: HLRDummyResolver [
<category: 'OsmoMSC-Tests'>
insertSubscriber: aIMSI [ ^ true ]
]

35
tests/HLRTest.st Normal file
View File

@ -0,0 +1,35 @@
"
(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/>.
"
TestCase subclass: HLRTest [
<category: 'OsmoMSC-Tests'>
testHLRFind [
| hlr sub |
hlr := HLRLocalCollection new.
hlr addSubscriber: '123456'.
hlr addSubscriber: '345677'.
self deny: (hlr findSubscriberByIMSI: '123456') isNil.
self deny: (hlr findSubscriberByIMSI: '345677') isNil.
self assert: (hlr findSubscriberByIMSI: '432432') isNil.
sub := hlr findSubscriberByIMSI: '123456'.
self assert: sub imsi = '123456'.
]
]

View File

@ -0,0 +1,37 @@
"
(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/>.
"
TestCase subclass: MSCBSCConnectionHandlerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I should test the feature that each config can only
be connected once but that is not done yet. It requires some work
on socket code. TODO!!!'>
testOnlyOnce [
"
| msc socket bsc |
msc := MSCApplication new.
msc bscConfig addBSC: '127.0.0.1' withName: 'foo' andLac: 4711.
bsc := msc bscConfig bscList first.
socket := DummySocket new.
socket instVarNamed: #peer put: bsc peer.
socket instVarNamed: #closed put: false.
"
]
]

View File

@ -1,177 +0,0 @@
"
(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/>.
"
PackageLoader fileInPackage: 'SUnit'.
TestCase subclass: HLRTest [
<category: 'OsmoMSC-Tests'>
testHLRFind [
| hlr sub |
hlr := HLRLocalCollection new.
hlr addSubscriber: '123456'.
hlr addSubscriber: '345677'.
self deny: (hlr findSubscriberByIMSI: '123456') isNil.
self deny: (hlr findSubscriberByIMSI: '345677') isNil.
self assert: (hlr findSubscriberByIMSI: '432432') isNil.
sub := hlr findSubscriberByIMSI: '123456'.
self assert: sub imsi = '123456'.
]
]
HLRResolver subclass: HLRDummyResolver [
<category: 'OsmoMSC-Tests'>
insertSubscriber: aIMSI [ ^ true ]
]
TestCase subclass: VLRTest [
<category: 'OsmoMSC-Tests'>
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.
]
]
TestCase subclass: BSCConfigTest [
<category: 'OsmoMSC-Tests'>
<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 deny: item1 connected.
self assert: item2 name = 'test2'.
self assert: item2 peer = addr.
self assert: item2 lac = -1.
self deny: item2 connected.
]
testConfig [
| cfg |
"Test that adding stuff again is refused"
cfg := BSCConfig new.
self shouldnt:
[cfg addBSC: '127.0.0.1' withName: 'abc1' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Simply adding it'.
self should:
[cfg addBSC: '127.0.0.1' withName: 'abc2' andLac: 1123 sendOsmoRSIP: false]
raise: Exception description: 'Same IP is forbidden'.
self should:
[cfg addBSC: '127.0.0.2' withName: 'abc3' andLac: 2311 sendOsmoRSIP: false]
raise: Exception description: 'Different IP same lac'.
self shouldnt:
[cfg addBSC: '127.0.0.2' withName: 'abc4' andLac: 1123 sendOsmoRSIP: false]
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'.
]
]
TestCase subclass: BSCListenerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'Test some basic socket functionality'>
testListenAndStop [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
'Will attempt to stop the connection' printNl.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
"Test that it will work again"
'Will attempt to stop the connection2' printNl.
listener start.
[(Delay forSeconds: 2) wait. listener stop] fork.
res := listener serve.
self deny: res.
]
testListenOnDeadSocket [
| listener res |
listener := BSCListener initWith: '127.0.0.1' port: 9245 handler: nil.
listener stop.
res := listener serve.
self deny: res.
]
]
TestCase subclass: MSCBSCConnectionHandlerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I should test the feature that each config can only
be connected once but that is not done yet. It requires some work
on socket code. TODO!!!'>
testOnlyOnce [
"
| msc socket bsc |
msc := MSCApplication new.
msc bscConfig addBSC: '127.0.0.1' withName: 'foo' andLac: 4711.
bsc := msc bscConfig bscList first.
socket := DummySocket new.
socket instVarNamed: #peer put: bsc peer.
socket instVarNamed: #closed put: false.
"
]
]
TestCase subclass: BSCIPAConnectionTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I just do some simple smoke testing here'>
testSmoke [
| ipa |
ipa := BSCIPAConnection
createOn: 'hi' writeStream
withConfig: (BSCConfigItem initWith: '0.0.0.0' name: 'foo')
msc: nil.
]
]

38
tests/VLRTest.st Normal file
View File

@ -0,0 +1,38 @@
"
(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/>.
"
TestCase subclass: VLRTest [
<category: 'OsmoMSC-Tests'>
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.
]
]