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

Merge branch 'zecke/gsm-auth'

This adds the authenticator features to the MSC. It sits on the
disk for far too long. So let's just merge this and be done with
it.
This commit is contained in:
Holger Hans Peter Freyther 2014-03-13 09:20:24 +01:00
commit 69ca1cbe52
13 changed files with 618 additions and 44 deletions

View File

@ -6,10 +6,14 @@ Eval [
fileIn: 'src/BSCConfig.st';
fileIn: 'src/BSCListener.st';
fileIn: 'src/BSCSCCPHandler.st';
fileIn: 'src/GSMAuthenticator.st';
fileIn: 'src/GSMProcessor.st';
fileIn: 'src/GSMMOCall.st';
fileIn: 'src/GSMLURequest.st';
fileIn: 'src/GSMCMServiceRequest.st';
fileIn: 'src/GSMEmergencySetup.st';
fileIn: 'src/BSCIPAConnection.st';
fileIn: 'src/PagingManager.st';
fileIn: 'src/MSC.st';
fileIn: 'src/SIPCall.st'.

View File

@ -11,9 +11,13 @@
<filein>src/BSCConfig.st</filein>
<filein>src/BSCListener.st</filein>
<filein>src/BSCSCCPHandler.st</filein>
<filein>src/GSMAuthenticator.st</filein>
<filein>src/GSMProcessor.st</filein>
<filein>src/GSMCMServiceRequest.st</filein>
<filein>src/GSMMOCall.st</filein>
<filein>src/GSMLURequest.st</filein>
<filein>src/GSMEmergencySetup.st</filein>
<filein>src/PagingManager.st</filein>
<filein>src/BSCIPAConnection.st</filein>
<filein>src/MSC.st</filein>
<filein>src/SIPCall.st</filein>
@ -25,6 +29,9 @@
<sunit>OsmoMSC.BSCListenerTest</sunit>
<sunit>OsmoMSC.MSCBSCConnectionHandlerTest</sunit>
<sunit>OsmoMSC.BSCIPAConnectionTest</sunit>
<sunit>OsmoMSC.AuthTestNull</sunit>
<sunit>OsmoMSC.AuthTestIdentity</sunit>
<filein>tests/Test.st</filein>
<filein>tests/AuthTest.st</filein>
</test>
</package>

View File

@ -1,5 +1,5 @@
"
(C) 2010-2012 by Holger Hans Peter Freyther
(C) 2010-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -19,7 +19,7 @@
PackageLoader fileInPackage: #Sockets.
Object subclass: BSCConfigItem [
| peer token name lac connected osmoExtension |
| peer token name lac connection osmoExtension |
<category: 'OsmoMSC-BSC'>
<comment: 'I hold the configuration for one BSC Item. It consists of the
@ -29,7 +29,7 @@ peer address, the lac, if it is connected'>
^ self new
peer: aPeer;
name: aName;
connected: false;
connection: nil;
sendOsmoRSIP: false;
lac: -1;
yourself
@ -60,10 +60,19 @@ peer address, the lac, if it is connected'>
lac := aLac.
]
connected [ <category: 'accessing'> ^ connected ]
connected: aState [
connected [
<category: 'accessing'>
^ connection isNil not
]
connection: aCon [
<category: 'private'>
connected := aState.
connection := aCon.
]
connection [
<category: 'private'>
^ connection
]
sendOsmoRSIP [ <category: 'accessing'> ^ osmoExtension ]

View File

@ -1,5 +1,5 @@
"
(C) 2010-2011 by Holger Hans Peter Freyther
(C) 2010-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -86,6 +86,13 @@ Object subclass: BSCConnection [
command: Osmo.MGCPOsmoRSIPCommand createRSIP;
startSingleShot.
]
sendUdt: aMsg [
| udt addr |
addr := Osmo.SCCPAddress createWith: 254.
udt := Osmo.SCCPUDT initWith: addr calling: addr data: aMsg.
^ self send: udt toMessage with:Osmo.IPAConstants protocolSCCP.
]
]
BSCConnection subclass: BSCIPAConnection [

View File

@ -22,13 +22,33 @@ Object subclass: GSMAuthenticatorBase [
<comment: 'I am the base class for authenticating a given
subscriber. My subclasses can either allow everyone, store
the IMSI and IMEI or be fully GSM compliant and ask a HLR
for an authentication tuple.'>
for an authentication tuple.
When calling the callbacks make sure to go through the
connection>>#takeLocks: selector to take the required locks.'>
<import: OsmoGSM>
LegalMessages := {OsmoGSM.GSM48CMServiceReq.
OsmoGSM.GSM48RRPagingResponse.
OsmoGSM.GSM48LURequest.
"As part of Local-Call-Routing deal with CC Setup"
OsmoGSM.GSM48CCSetup.
}.
appropriateInitialMessage: aMsg [
"Check if the message is one of the allowed initial messages."
^ LegalMessages includes: aMsg class
]
connection: aCon [
<category: 'creation'>
connection := aCon.
]
connection [
<category: 'access'>
^ connection
]
onAccept: aBlock [
<category: 'creation'>
"Called when the connection is accepted"
@ -58,6 +78,11 @@ Object subclass: GSMAuthenticatorBase [
"The GSM Connection has failed cancel everything."
^ self subclassResponsibility
]
nextPut: aMsg [
connection nextPutData: (BSSAPDTAP initWith: aMsg
linkIdentifier: 0).
]
]
GSMAuthenticatorBase subclass: GSMNullAuthenticator [
@ -65,7 +90,9 @@ GSMAuthenticatorBase subclass: GSMNullAuthenticator [
<comment: 'I accept everything...'>
start: aMsg [
onAccept value: self.
(self appropriateInitialMessage: aMsg)
ifTrue: [onAccept value: self]
ifFalse: [onReject value: self].
]
onData: aMsg [
@ -76,3 +103,73 @@ GSMAuthenticatorBase subclass: GSMNullAuthenticator [
"Nothing"
]
]
GSMAuthenticatorBase subclass: GSMIdentityAuthenticator [
| state timeout |
<category: 'OsmoMSC-GSM-Authentication'>
<comment: 'I query for the IMSI and IMEI but do this in an insecure
way and will never switch on the crypto. I will ask for the IMSI and
IMEI'>
cancel [
"Cancel all timers"
timeout ifNotNil: [timeout cancel. timeout := nil].
]
reject: aMsg [
<category: 'reject'>
self logError: 'GSMIdentityAuthenticator(srcref:%1) rejecting type %2'
% {connection srcRef. aMsg class} area: #bsc.
state := #rejected:.
onReject value: self.
]
start: aMsg [
"TODO we could take the IMSI from the first message but this
is mostly for educational purpose."
(self appropriateInitialMessage: aMsg)
ifTrue: [self askForIMSI]
ifFalse: [self reject: aMsg].
]
askForIMSI [
| req |
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [self timeOut].
"I ask for the IMSI."
req := GSM48IdentityReq new.
req idType type: GSM48IdentityType typeIMSI.
state := #askForIMSI:.
self nextPut: req toMessage.
]
askForIMSI: aIdResponse [
connection
addInfo: 'IMSI'
value: aIdResponse mi imsi.
self logNotice: 'GSMIdentityAuthenticator(srcref:%1) got IMSI(%2).'
% {connection srcRef. aIdResponse mi imsi} area: #bsc.
timeout cancel.
onAccept value: self.
]
onData: aMsg [
[
self perform: state with: aMsg.
] on: Exception do: [:e |
e logException: 'GSMIdentityAuthenticator(srcref:%1) failed dispatch.'
% {connection srcRef} area: #bsc.
timeout cancel.
onReject value: self.
].
]
timeOut [
self logError: 'GSMIdentityAuthenticator(srcref:%1) no reply to %2'
% {connection srcRef. state} area: #bsc.
state := #timedout:.
connection takeLocks: [onReject value: self].
]
]

108
src/GSMCMServiceRequest.st Normal file
View File

@ -0,0 +1,108 @@
"
(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/>.
"
OsmoGSM.GSM48CMServiceReq extend [
openTransactionOn: aCon sapi: aSapi [
| tran |
<category: '*OsmoMSC-GSM'>
"This is weird. We can accept or reject the service."
tran := (GSMCMServiceRequest on: aSapi with: self ti)
con: aCon; yourself.
aCon openTransaction: tran with: self.
]
]
OsmoGSM.GSM48MSG extend [
dispatchForCMOn: aCon [
<category: '*OsmoMSC-GSM'>
self logError: '%1(srcref:%2) unknown dispatch for CM Service Request'
% {self class. aCon srcref} with: #bsc.
^ false
]
]
OsmoGSM.GSM48CCEmergencySetup extend [
dispatchForCMOn: aCM [
| call |
<category: '*OsmoMSC-GSM'>
"Start the Emergency Call"
call := (GSMEmergencyCall on: 0 with: self ti)
con: aCM con; yourself.
aCM con openTransaction: call with: self.
"The CMServiceRequest transaction can go away now."
^ true
]
]
GSMTransaction subclass: GSMCMServiceRequest [
| timeout service state |
<category: 'OsmoMSC-GSM'>
<comment: 'I am used by the MS to ask for a service. I can check
if we want to have this service and Accept/Reject it. Atfer this
I need to wait a bit for the actual service to be started.'>
GSMCMServiceRequest class >> stateNull [ <category: 'states'> ^ #null ]
GSMCMServiceRequest class >> stateWaitService [ <category: 'states'> ^ #service ]
canHandle: aMsg sapi: aSapi [
"TODO: check if there are other transactions that should be called? Or
deal with it differently?"
^ true
]
initialize [
<category: 'creation'>
state := self class stateNull.
]
start: aCMServiceRequest [
| accept |
state := self class stateWaitService.
accept := OsmoGSM.GSM48CMServiceAccept new.
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [con takeLocks: [self timeOut]].
self nextPutSapi: accept.
]
dispatch: aMsg [
| res |
"I am now getting the real MO-request. Let's see how we can
morph it into a real request."
res := aMsg dispatchForCMOn: self.
res ifFalse: [^self].
"We are done. Remove ourselves from the list."
timeout cancel.
con removeTransaction: self
]
cancel [
timeout cancel.
^ super cancel
]
timeOut [
self logError: 'GSMCMServiceRequest(srcref:%1) timeout in state %2'
% {con srcRef. state} area: #bsc.
con removeTransaction: self.
]
]

33
src/GSMEmergencySetup.st Normal file
View File

@ -0,0 +1,33 @@
"
(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/>.
"
GSMMOCall subclass: GSMEmergencyCall [
<category: 'OsmoMSC-GSM'>
<comment: 'I handle emergency calls'>
selectAudioRoute: aCCMessage [
"select route for this call, or release the call"
remoteLeg := con selectAudioRouteForEmergency: self.
remoteLeg isNil ifTrue: [
self logError:
'GSMEmergencyCall(srcref:%1) failed to select audio route.'
% {con srcRef} area: #bsc.
self releaseComplete.
].
]
]

View File

@ -23,7 +23,7 @@ PackageLoader
OsmoGSM.GSM48LURequest extend [
openTransactionOn: aCon sapi: aSapi [
| tran |
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
'foo' printNl.
tran := (GSMLURequest on: aSapi with: self ti)
@ -47,13 +47,15 @@ GSMTransaction subclass: GSMLURequest [
start: aCCMessage [
<category: 'start'>
aCCMessage inspect.
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [self timeOut].
self logNotice: 'GSMLURequest(srcref:%1) starting LU'
% {con srcRef} area: #bsc.
timeout := Osmo.TimerScheduler instance
scheduleInSeconds: 5 block: [con takeLocks: [self timeOut]].
]
timeOut [
self logError: 'GSMLURequest(srcref:%1) timeout.' % {con srcRef} area: #bsc.
self nextPutSapi: OsmoGSM.GSM48LUReject new.
con removeTransaction: self.
]
]

View File

@ -18,42 +18,42 @@
OsmoGSM.GSM48MSG extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moUnknown: self.
]
]
OsmoGSM.GSM48CCConnectAck extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moConnectAck: self.
]
]
OsmoGSM.GSM48CCDisconnect extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moDisconnect: self.
]
]
OsmoGSM.GSM48CCRelease extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moRelease: self.
]
]
OsmoGSM.GSM48CCReleaseCompl extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moReleaseCompl: self.
]
]
OsmoGSM.GSM48CCStatus extend [
dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon moStatus: self.
]
]
@ -61,7 +61,7 @@ OsmoGSM.GSM48CCStatus extend [
OsmoGSM.GSM48CCSetup extend [
openTransactionOn: aCon sapi: aSapi [
| tran |
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
tran := (GSMMOCall on: aSapi with: self ti)
con: aCon;
yourself.
@ -244,9 +244,7 @@ GSMTransaction subclass: GSMMOCall [
con removeTransaction: self.
]
start: aCCMessage [
<category: 'transaction'>
selectAudioRoute: aCCMessage [
"select route for this call, or release the call"
remoteLeg := con selectAudioRoute: aCCMessage calledOrDefault leg: self.
remoteLeg isNil ifTrue: [
@ -254,8 +252,14 @@ GSMTransaction subclass: GSMMOCall [
'GSMMOCall(srcref:%1) failed to select audio route.'
% {con srcRef} area: #bsc.
self releaseComplete.
^ self
].
]
start: aCCMessage [
<category: 'transaction'>
self selectAudioRoute: aCCMessage.
remoteLeg isNil ifTrue: [^self].
"Failed to allocate an endpoint"
con allocateEndpoint isNil ifTrue: [

View File

@ -20,19 +20,19 @@ PackageLoader fileInPackage: 'OsmoGSM'.
OsmoGSM.BSSAPMessage extend [
dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon bssapUnknownData: self
]
]
OsmoGSM.BSSAPManagement extend [
dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
self dispatchMAP: aCon.
]
dispatchMAP: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
(Dictionary from: {
OsmoGSM.GSM0808Helper msgComplL3 -> #mapLayer3:.
OsmoGSM.GSM0808Helper msgClearReq -> #mapClearReq:.
@ -51,14 +51,14 @@ OsmoGSM.BSSAPManagement extend [
OsmoGSM.BSSAPDTAP extend [
dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
aCon dispatchDTAP: self.
]
]
OsmoGSM.GSM48MSG extend [
openTransactionOn: aCon sapi: aSapi [
<category: '*-OsmoMSC-GSM'>
<category: '*OsmoMSC-GSM'>
self logError: 'Can not open transaction for %1' % {self class} area: #bsc.
]
]
@ -79,6 +79,10 @@ GSM transaction on a given SAPI'>
yourself
]
canHandle: aMsg sapi: aSapi [
^ self sapi = aSapi and: [self ti = aMsg ti].
]
sapi [
<category: 'accessing'>
^ sapi
@ -95,6 +99,11 @@ GSM transaction on a given SAPI'>
con := aCon.
]
con [
<category: 'creation'>
^ con
]
assignmentFailure [
"The audio assignment has failed."
]
@ -127,7 +136,7 @@ GSM transaction on a given SAPI'>
]
OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [
| transactions state endp connId mgcp_trans auth pending |
| transactions state endp connId mgcp_trans auth pending info |
<category: 'OsmoMSC-GSM'>
<comment: 'I am driving a SCCP Connection. This consists of being
@ -142,7 +151,7 @@ hosting various transactions and dispatching to them.'>
GSMProcessor class >> authenticator [
<category: 'authenticator'>
^ GSMNullAuthenticator
^ GSMIdentityAuthenticator
]
GSMProcessor class >> createAssignment: aMul timeslot: aTs [
@ -164,9 +173,16 @@ hosting various transactions and dispatching to them.'>
<category: 'creation'>
transactions := OrderedCollection new.
state := self class stateInitial.
info := Dictionary new.
^ super initialize.
]
addInfo: aKey value: aValue [
<category: 'misc'>
"Store additional info about this call here."
info at: aKey put: aValue.
]
data: aData [
| msg bssmap data |
<category: 'input'>
@ -312,7 +328,7 @@ hosting various transactions and dispatching to them.'>
self addTransaction: aTran.
"The authentication has happend, just start the transaction."
self state = self class stateAuth ifTrue: [
state = self class stateAuth ifTrue: [
^ aTran start: aMsg
].
@ -331,10 +347,10 @@ hosting various transactions and dispatching to them.'>
auth := self class authenticator new
connection: self;
onAccept: [:auth | self takeLocks: [ self authenticationAccepted]];
onReject: [:auth | self takeLocks: [ self authenticationRejected]];
onAccept: [:auth | self authenticationAccepted];
onReject: [:auth | self authenticationRejected];
yourself.
auth start.
auth start: aMsg.
]
addTransaction: aTran [
@ -370,9 +386,12 @@ hosting various transactions and dispatching to them.'>
^ auth onData: aMsg.
].
"Find an active transaction for this"
"Find an active transaction for this. TODO: For CM Service Request
we need to hand everything there. With multiple transactions we
should have a ranking. E.g. with bi-directional SMS this needs to be
handled specially. We need the existing transaction to take preference."
transactions do: [:each |
(each sapi = aSapi and: [each ti = aMsg ti]) ifTrue: [
(each canHandle: aMsg sapi: aSapi) ifTrue: [
each dispatch: aMsg.
self checkRelease.
^ true.
@ -430,6 +449,12 @@ hosting various transactions and dispatching to them.'>
^ conManager msc mgcpCallAgent
]
selectAudioRouteForEmergency: aLeg [
<category: 'call'>
^ conManager msc
selectAudioRouteForEmergency: self leg: aLeg.
]
selectAudioRoute: aPlan leg: aLeg [
<category: 'call'>
^ conManager msc
@ -707,7 +732,9 @@ hosting various transactions and dispatching to them.'>
authenticationAccepted [
<category: 'auth'>
"Must be locked"
"TODO: where to start the encryption? CM Service Accept/Ciphering Command?"
auth := nil.
state := self class stateAuth.
pending do: [:each |
each key start: each value].
pending := nil.
@ -718,7 +745,8 @@ hosting various transactions and dispatching to them.'>
"Must be locked"
"TODO"
"Send a CM Service Request to the phone"
"Send a CM Service Reject/LU Reject to the phone. Probably the
transaction should reject it."
"Close down the connection. FIXME: use a better error value"
self clearCommand: 0.

View File

@ -1,5 +1,5 @@
"
(C) 2010-2011 by Holger Hans Peter Freyther
(C) 2010-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -110,11 +110,11 @@ Object subclass: MSCBSCConnectionHandler [
Processor activeProcess name: 'MSCBSCConnectionHandler(%1)' % {aConfig lac}.
[[
aConfig connected: true.
aConfig connection: bsc.
self connections add: bsc.
bsc process.
] on: SystemExceptions.EndOfStream do: [:ex |
aConfig connected: false.
aConfig connection: nil.
self logNotice: 'BSC disconnected for lac: %1' % {aConfig lac}
area: #bsc.
] on: Exception do: [:ex |
@ -129,7 +129,7 @@ Object subclass: MSCBSCConnectionHandler [
self logError: 'BSC was never added on lac: %1?' % {aConfig lac}
area: #bsc].
aConfig connected: false.
aConfig connection: nil.
aConnection close.
].
] fork.
@ -160,7 +160,7 @@ Object subclass: MSCBSCConnectionHandler [
]
Object subclass: MSCApplication [
| hlr vlr config bscListener bscConfig bscConHandler mgcp sip |
| hlr vlr config bscListener bscConfig bscConHandler mgcp sip paging |
<category: 'OsmoMSC-MSC'>
<comment: 'I am a MSC as I have the VLR/HLR and other instances'>
@ -190,6 +190,8 @@ Object subclass: MSCApplication [
hlr [ ^ hlr ifNil: [HLRLocalCollection new]]
vlr [ ^ vlr ifNil: [VLRLocalCollection new]]
pagingManager [ ^ paging ifNil: [paging := PagingManager initWith: self]]
config [ ^ config ifNil: [config := MSCConfig new]]
bscConfig [ ^ bscConfig ifNil: [bscConfig := BSCConfig new]]
bscConHandler [ ^ bscConHandler ifNil: [bscConHandler := MSCBSCConnectionHandler initWith: self]]
@ -245,6 +247,18 @@ Object subclass: MSCApplication [
sip]
]
selectAudioRouteForEmergency: aCon leg: aLeg [
^ (SIPMTCall
fromUser: 'sip:1000@sip.zecke.osmocom.org'
host: '127.0.0.1'
port: 5060
to: 'sip:911@127.0.0.1'
on: self sipGateway)
remoteLeg: aLeg;
yourself
]
selectAudioRoute: aCon plan: aPlan leg: aLeg [
| nr |
"TODO: Very simple and hardcoded rule"
@ -287,7 +301,7 @@ Object subclass: MSCApplication [
bscPort: 5000;
sipIP: '127.0.0.1'.
msc bscConfig
addBSC: '127.0.0.1' withName: 'test1' andLac: 4711 sendOsmoRSIP: true;
addBSC: '127.0.0.1' withName: 'test1' andLac: 8210 sendOsmoRSIP: true;
addBSC: '10.240.240.1' withName: 'test2' andLac: 4712 sendOsmoRSIP: true.
msc returnedFromSnapshot.

68
src/PagingManager.st Normal file
View File

@ -0,0 +1,68 @@
"
(C) 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: PagingManager [
| msc |
<category: 'OsmoMSC-GSM'>
PagingManager class >> initWith: aMsc [
^ self new
instVarNamed: #msc put: aMsc;
yourself.
]
pageAll: anImsi [
<category: 'paging'>
"Page a subscriber on all LACs of all BSCs"
msc bscConfig bscList do: [:bscConfig |
"This can race with a disconnect but that is fine."
bscConfig connected ifTrue: [
OsmoDispatcher dispatchBlock: [
self pageBSC: bscConfig with: anImsi]]].
]
pageBSC: aBscConfig with: anImsi [
| connection cmd |
<category: 'paging'>
"Page a single BSC"
"Is the bsc still connected?"
connection := aBscConfig connection.
connection ifNil: [
^ false
].
cmd := self createPagingCommand: aBscConfig lac with: anImsi.
connection sendUdt: cmd toMessage asByteArray.
]
createPagingCommand: aLac with: anImsi [
| cmd |
cmd := OsmoGSM.IEMessage initWith: OsmoGSM.GSM0808Helper msgPaging.
cmd
addIe: (OsmoGSM.GSM0808IMSI initWith: anImsi);
addIe: (OsmoGSM.GSM0808CellIdentifierList new
ident: OsmoGSM.GSM0808CellIdentifierList cellLocationAreaCode;
cells: (Array with: aLac);
yourself);
yourself.
^ OsmoGSM.BSSAPManagement initWith: cmd toMessage
]
]

193
tests/AuthTest.st Normal file
View File

@ -0,0 +1,193 @@
"
(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.
]
]
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.'>
testWrongResponse [
| auth rejected wait |
Transcript nextPutAll: 'Going to send a wrong response leading to an exception.'; nl.
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockForAuthCheat initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
]
testTimeout [
| auth rejected wait |
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockForAuthTimeout initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
]
testIMSI [
| auth accept wait |
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | self assert: a = auth. accept := true. wait signal];
onReject: [:a | ^self error: 'This should not be rejected'];
yourself.
auth
connection: (GSMProcessorMockForAuthIMSI initWith: auth);
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: accept.
self assert: (auth connection getInfo: 'IMSI') = auth connection usedIMSI.
]
testWrongInitialMessage [
| auth rejected wait |
Transcript nextPutAll: 'Going to send an initial message'; nl.
wait := Semaphore new.
auth := GSMIdentityAuthenticator new
onAccept: [:a | ^self error: 'This should not be accepted'];
onReject: [:a | self assert: a = auth. rejected := true. wait signal];
yourself.
auth
connection: (GSMProcessorMockBase initWith: auth);
start: OsmoGSM.GSM48IdentityReq new.
wait wait.
self assert: rejected.
]
]