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

auth: Make the authenticator more strict and check the initial message.

The initial message needs to be one that is specified in GSM 08.08. We
do not support all of the messages yet but it is a start. On top of that
we also support to start with a CC Setup message.
This commit is contained in:
Holger Hans Peter Freyther 2012-12-03 17:58:21 +01:00 committed by Holger Hans Peter Freyther
parent 587c1c3683
commit 8f7a9ea8a5
2 changed files with 68 additions and 8 deletions

View File

@ -25,6 +25,19 @@ Object subclass: GSMAuthenticatorBase [
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'>
@ -67,7 +80,7 @@ Object subclass: GSMAuthenticatorBase [
]
nextPut: aMsg [
connection nextPutData: (OsmoGSM.BSSAPDTAP initWith: aMsg
connection nextPutData: (BSSAPDTAP initWith: aMsg
linkIdentifier: 0).
]
]
@ -77,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 [
@ -91,7 +106,6 @@ GSMAuthenticatorBase subclass: GSMNullAuthenticator [
GSMAuthenticatorBase subclass: GSMIdentityAuthenticator [
| state timeout |
<import: OsmoGSM>
<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
@ -102,10 +116,20 @@ GSMAuthenticatorBase subclass: GSMIdentityAuthenticator [
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 askForIMSI.
(self appropriateInitialMessage: aMsg)
ifTrue: [self askForIMSI]
ifFalse: [self reject: aMsg].
]
askForIMSI [

View File

@ -26,9 +26,27 @@ TestCase subclass: AuthTestNull [
onAccept: [:a| self assert: a = auth. accepted := true];
onReject: [:a| self shouldNotImplement];
yourself.
auth start: nil.
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 [
@ -109,7 +127,7 @@ TestCase subclass: AuthTestIdentity [
yourself.
auth
connection: (GSMProcessorMockForAuthCheat initWith: auth);
start: nil.
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
@ -124,7 +142,7 @@ TestCase subclass: AuthTestIdentity [
yourself.
auth
connection: (GSMProcessorMockForAuthTimeout initWith: auth);
start: nil.
start: OsmoGSM.GSM48CMServiceReq new.
wait wait.
self assert: rejected.
@ -139,10 +157,28 @@ TestCase subclass: AuthTestIdentity [
yourself.
auth
connection: (GSMProcessorMockForAuthIMSI initWith: auth);
start: nil.
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.
]
]