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

auth: Introduce an authenticator that asks for the IMSI

This commit is contained in:
Holger Hans Peter Freyther 2012-12-02 00:14:57 +01:00 committed by Holger Hans Peter Freyther
parent 7382efcf16
commit 587c1c3683
4 changed files with 197 additions and 2 deletions

View File

@ -27,6 +27,7 @@
<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>

View File

@ -31,6 +31,11 @@ Object subclass: GSMAuthenticatorBase [
connection := aCon.
]
connection [
<category: 'access'>
^ connection
]
onAccept: aBlock [
<category: 'creation'>
"Called when the connection is accepted"
@ -60,6 +65,11 @@ Object subclass: GSMAuthenticatorBase [
"The GSM Connection has failed cancel everything."
^ self subclassResponsibility
]
nextPut: aMsg [
connection nextPutData: (OsmoGSM.BSSAPDTAP initWith: aMsg
linkIdentifier: 0).
]
]
GSMAuthenticatorBase subclass: GSMNullAuthenticator [
@ -78,3 +88,64 @@ GSMAuthenticatorBase subclass: GSMNullAuthenticator [
"Nothing"
]
]
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
IMEI'>
cancel [
"Cancel all timers"
timeout ifNotNil: [timeout cancel. timeout := nil].
]
start: aMsg [
"TODO we could take the IMSI from the first message but this
is mostly for educational purpose."
self askForIMSI.
]
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].
]
]

View File

@ -127,7 +127,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 +142,7 @@ hosting various transactions and dispatching to them.'>
GSMProcessor class >> authenticator [
<category: 'authenticator'>
^ GSMNullAuthenticator
^ GSMIdentityAuthenticator
]
GSMProcessor class >> createAssignment: aMul timeslot: aTs [
@ -164,9 +164,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'>

View File

@ -30,3 +30,119 @@ TestCase subclass: AuthTestNull [
self assert: accepted.
]
]
Object subclass: GSMProcessorMockBase [
| auth dict |
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 [
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 [
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 [
nextPutData: aData [
"Do nothing"
]
]
TestCase subclass: AuthTestIdentity [
<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: nil.
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: nil.
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: nil.
wait wait.
self assert: accept.
self assert: (auth connection getInfo: 'IMSI') = auth connection usedIMSI.
]
]